-- Do not edit! Automatically generated by create-lapack-ffi.
{-# LANGUAGE ForeignFunctionInterface #-}
module Numeric.LAPACK.FFI.ComplexDouble where

import Data.Complex (Complex)
import Foreign.Ptr (FunPtr, Ptr)
import Foreign.C.Types


-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zbbcsd.f>
foreign import ccall "zbbcsd_"
   bbcsd :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zbdsqr.f>
foreign import ccall "zbdsqr_"
   bdsqr :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zcgesv.f>
foreign import ccall "zcgesv_"
   cgesv :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Float) -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zcposv.f>
foreign import ccall "zcposv_"
   cposv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Float) -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgbbrd.f>
foreign import ccall "zgbbrd_"
   gbbrd :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgbcon.f>
foreign import ccall "zgbcon_"
   gbcon :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgbequ.f>
foreign import ccall "zgbequ_"
   gbequ :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgbequb.f>
foreign import ccall "zgbequb_"
   gbequb :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgbrfs.f>
foreign import ccall "zgbrfs_"
   gbrfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgbsv.f>
foreign import ccall "zgbsv_"
   gbsv :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgbsvx.f>
foreign import ccall "zgbsvx_"
   gbsvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CChar -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgbtf2.f>
foreign import ccall "zgbtf2_"
   gbtf2 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgbtrf.f>
foreign import ccall "zgbtrf_"
   gbtrf :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgbtrs.f>
foreign import ccall "zgbtrs_"
   gbtrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgebak.f>
foreign import ccall "zgebak_"
   gebak :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgebal.f>
foreign import ccall "zgebal_"
   gebal :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgebd2.f>
foreign import ccall "zgebd2_"
   gebd2 :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgebrd.f>
foreign import ccall "zgebrd_"
   gebrd :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgecon.f>
foreign import ccall "zgecon_"
   gecon :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeequ.f>
foreign import ccall "zgeequ_"
   geequ :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeequb.f>
foreign import ccall "zgeequb_"
   geequb :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgees.f>
foreign import ccall "zgees_"
   gees :: Ptr CChar -> Ptr CChar -> FunPtr (Ptr (Complex Double) -> IO Bool) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Bool -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeesx.f>
foreign import ccall "zgeesx_"
   geesx :: Ptr CChar -> Ptr CChar -> FunPtr (Ptr (Complex Double) -> IO Bool) -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Bool -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeev.f>
foreign import ccall "zgeev_"
   geev :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeevx.f>
foreign import ccall "zgeevx_"
   geevx :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgehd2.f>
foreign import ccall "zgehd2_"
   gehd2 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgehrd.f>
foreign import ccall "zgehrd_"
   gehrd :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgelq2.f>
foreign import ccall "zgelq2_"
   gelq2 :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgelqf.f>
foreign import ccall "zgelqf_"
   gelqf :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgels.f>
foreign import ccall "zgels_"
   gels :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgelsd.f>
foreign import ccall "zgelsd_"
   gelsd :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgelss.f>
foreign import ccall "zgelss_"
   gelss :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgelsy.f>
foreign import ccall "zgelsy_"
   gelsy :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeql2.f>
foreign import ccall "zgeql2_"
   geql2 :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeqlf.f>
foreign import ccall "zgeqlf_"
   geqlf :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeqp3.f>
foreign import ccall "zgeqp3_"
   geqp3 :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeqr2.f>
foreign import ccall "zgeqr2_"
   geqr2 :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeqr2p.f>
foreign import ccall "zgeqr2p_"
   geqr2p :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeqrf.f>
foreign import ccall "zgeqrf_"
   geqrf :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeqrfp.f>
foreign import ccall "zgeqrfp_"
   geqrfp :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgerfs.f>
foreign import ccall "zgerfs_"
   gerfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgerq2.f>
foreign import ccall "zgerq2_"
   gerq2 :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgerqf.f>
foreign import ccall "zgerqf_"
   gerqf :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgesc2.f>
foreign import ccall "zgesc2_"
   gesc2 :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr Double -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgesdd.f>
foreign import ccall "zgesdd_"
   gesdd :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgesv.f>
foreign import ccall "zgesv_"
   gesv :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgesvd.f>
foreign import ccall "zgesvd_"
   gesvd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgesvx.f>
foreign import ccall "zgesvx_"
   gesvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CChar -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgetc2.f>
foreign import ccall "zgetc2_"
   getc2 :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgetf2.f>
foreign import ccall "zgetf2_"
   getf2 :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgetrf.f>
foreign import ccall "zgetrf_"
   getrf :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgetri.f>
foreign import ccall "zgetri_"
   getri :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgetrs.f>
foreign import ccall "zgetrs_"
   getrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zggbak.f>
foreign import ccall "zggbak_"
   ggbak :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zggbal.f>
foreign import ccall "zggbal_"
   ggbal :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgges.f>
foreign import ccall "zgges_"
   gges :: Ptr CChar -> Ptr CChar -> Ptr CChar -> FunPtr (Ptr (Complex Double) -> Ptr (Complex Double) -> IO Bool) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Bool -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zggesx.f>
foreign import ccall "zggesx_"
   ggesx :: Ptr CChar -> Ptr CChar -> Ptr CChar -> FunPtr (Ptr (Complex Double) -> Ptr (Complex Double) -> IO Bool) -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Bool -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zggev.f>
foreign import ccall "zggev_"
   ggev :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zggevx.f>
foreign import ccall "zggevx_"
   ggevx :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Bool -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zggglm.f>
foreign import ccall "zggglm_"
   ggglm :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgghrd.f>
foreign import ccall "zgghrd_"
   gghrd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgglse.f>
foreign import ccall "zgglse_"
   gglse :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zggqrf.f>
foreign import ccall "zggqrf_"
   ggqrf :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zggrqf.f>
foreign import ccall "zggrqf_"
   ggrqf :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgtcon.f>
foreign import ccall "zgtcon_"
   gtcon :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgtrfs.f>
foreign import ccall "zgtrfs_"
   gtrfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgtsv.f>
foreign import ccall "zgtsv_"
   gtsv :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgtsvx.f>
foreign import ccall "zgtsvx_"
   gtsvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgttrf.f>
foreign import ccall "zgttrf_"
   gttrf :: Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgttrs.f>
foreign import ccall "zgttrs_"
   gttrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgtts2.f>
foreign import ccall "zgtts2_"
   gtts2 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhbev.f>
foreign import ccall "zhbev_"
   hbev :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhbevd.f>
foreign import ccall "zhbevd_"
   hbevd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhbevx.f>
foreign import ccall "zhbevx_"
   hbevx :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhbgst.f>
foreign import ccall "zhbgst_"
   hbgst :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhbgv.f>
foreign import ccall "zhbgv_"
   hbgv :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhbgvd.f>
foreign import ccall "zhbgvd_"
   hbgvd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhbgvx.f>
foreign import ccall "zhbgvx_"
   hbgvx :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhbtrd.f>
foreign import ccall "zhbtrd_"
   hbtrd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhecon.f>
foreign import ccall "zhecon_"
   hecon :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zheequb.f>
foreign import ccall "zheequb_"
   heequb :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zheev.f>
foreign import ccall "zheev_"
   heev :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zheevd.f>
foreign import ccall "zheevd_"
   heevd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zheevr.f>
foreign import ccall "zheevr_"
   heevr :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zheevx.f>
foreign import ccall "zheevx_"
   heevx :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhegs2.f>
foreign import ccall "zhegs2_"
   hegs2 :: Ptr CInt -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhegst.f>
foreign import ccall "zhegst_"
   hegst :: Ptr CInt -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhegv.f>
foreign import ccall "zhegv_"
   hegv :: Ptr CInt -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhegvd.f>
foreign import ccall "zhegvd_"
   hegvd :: Ptr CInt -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhegvx.f>
foreign import ccall "zhegvx_"
   hegvx :: Ptr CInt -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zherfs.f>
foreign import ccall "zherfs_"
   herfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhesv.f>
foreign import ccall "zhesv_"
   hesv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhesvx.f>
foreign import ccall "zhesvx_"
   hesvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zheswapr.f>
foreign import ccall "zheswapr_"
   heswapr :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhetd2.f>
foreign import ccall "zhetd2_"
   hetd2 :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhetf2.f>
foreign import ccall "zhetf2_"
   hetf2 :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhetrd.f>
foreign import ccall "zhetrd_"
   hetrd :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhetrf.f>
foreign import ccall "zhetrf_"
   hetrf :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhetri.f>
foreign import ccall "zhetri_"
   hetri :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhetri2.f>
foreign import ccall "zhetri2_"
   hetri2 :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhetri2x.f>
foreign import ccall "zhetri2x_"
   hetri2x :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhetrs.f>
foreign import ccall "zhetrs_"
   hetrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhetrs2.f>
foreign import ccall "zhetrs2_"
   hetrs2 :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhfrk.f>
foreign import ccall "zhfrk_"
   hfrk :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhgeqz.f>
foreign import ccall "zhgeqz_"
   hgeqz :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhpcon.f>
foreign import ccall "zhpcon_"
   hpcon :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhpev.f>
foreign import ccall "zhpev_"
   hpev :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhpevd.f>
foreign import ccall "zhpevd_"
   hpevd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhpevx.f>
foreign import ccall "zhpevx_"
   hpevx :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhpgst.f>
foreign import ccall "zhpgst_"
   hpgst :: Ptr CInt -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhpgv.f>
foreign import ccall "zhpgv_"
   hpgv :: Ptr CInt -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhpgvd.f>
foreign import ccall "zhpgvd_"
   hpgvd :: Ptr CInt -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhpgvx.f>
foreign import ccall "zhpgvx_"
   hpgvx :: Ptr CInt -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhprfs.f>
foreign import ccall "zhprfs_"
   hprfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhpsv.f>
foreign import ccall "zhpsv_"
   hpsv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhpsvx.f>
foreign import ccall "zhpsvx_"
   hpsvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhptrd.f>
foreign import ccall "zhptrd_"
   hptrd :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhptrf.f>
foreign import ccall "zhptrf_"
   hptrf :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhptri.f>
foreign import ccall "zhptri_"
   hptri :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhptrs.f>
foreign import ccall "zhptrs_"
   hptrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhsein.f>
foreign import ccall "zhsein_"
   hsein :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr Bool -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhseqr.f>
foreign import ccall "zhseqr_"
   hseqr :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ilazlc.f>
foreign import ccall "ilazlc_"
   ilalc :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO CInt

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ilazlr.f>
foreign import ccall "ilazlr_"
   ilalr :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO CInt

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/izmax1.f>
foreign import ccall "izmax1_"
   imax1 :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO CInt

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlabrd.f>
foreign import ccall "zlabrd_"
   labrd :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlacgv.f>
foreign import ccall "zlacgv_"
   lacgv :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlacn2.f>
foreign import ccall "zlacn2_"
   lacn2 :: Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlacon.f>
foreign import ccall "zlacon_"
   lacon :: Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlacp2.f>
foreign import ccall "zlacp2_"
   lacp2 :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlacpy.f>
foreign import ccall "zlacpy_"
   lacpy :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlacrm.f>
foreign import ccall "zlacrm_"
   lacrm :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlacrt.f>
foreign import ccall "zlacrt_"
   lacrt :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaed0.f>
foreign import ccall "zlaed0_"
   laed0 :: Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaed7.f>
foreign import ccall "zlaed7_"
   laed7 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaed8.f>
foreign import ccall "zlaed8_"
   laed8 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaein.f>
foreign import ccall "zlaein_"
   laein :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaesy.f>
foreign import ccall "zlaesy_"
   laesy :: Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaev2.f>
foreign import ccall "zlaev2_"
   laev2 :: Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlag2c.f>
foreign import ccall "zlag2c_"
   lag2c :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Float) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlags2.f>
foreign import ccall "zlags2_"
   lags2 :: Ptr Bool -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlagtm.f>
foreign import ccall "zlagtm_"
   lagtm :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlahef.f>
foreign import ccall "zlahef_"
   lahef :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlahqr.f>
foreign import ccall "zlahqr_"
   lahqr :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlahr2.f>
foreign import ccall "zlahr2_"
   lahr2 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaic1.f>
foreign import ccall "zlaic1_"
   laic1 :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlals0.f>
foreign import ccall "zlals0_"
   lals0 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlalsa.f>
foreign import ccall "zlalsa_"
   lalsa :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlalsd.f>
foreign import ccall "zlalsd_"
   lalsd :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlangb.f>
foreign import ccall "zlangb_"
   langb :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlange.f>
foreign import ccall "zlange_"
   lange :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlangt.f>
foreign import ccall "zlangt_"
   langt :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlanhb.f>
foreign import ccall "zlanhb_"
   lanhb :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlanhe.f>
foreign import ccall "zlanhe_"
   lanhe :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlanhf.f>
foreign import ccall "zlanhf_"
   lanhf :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlanhp.f>
foreign import ccall "zlanhp_"
   lanhp :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlanhs.f>
foreign import ccall "zlanhs_"
   lanhs :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlanht.f>
foreign import ccall "zlanht_"
   lanht :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlansb.f>
foreign import ccall "zlansb_"
   lansb :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlansp.f>
foreign import ccall "zlansp_"
   lansp :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlansy.f>
foreign import ccall "zlansy_"
   lansy :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlantb.f>
foreign import ccall "zlantb_"
   lantb :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlantp.f>
foreign import ccall "zlantp_"
   lantp :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlantr.f>
foreign import ccall "zlantr_"
   lantr :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlapll.f>
foreign import ccall "zlapll_"
   lapll :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlapmr.f>
foreign import ccall "zlapmr_"
   lapmr :: Ptr Bool -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlapmt.f>
foreign import ccall "zlapmt_"
   lapmt :: Ptr Bool -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqgb.f>
foreign import ccall "zlaqgb_"
   laqgb :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CChar -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqge.f>
foreign import ccall "zlaqge_"
   laqge :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CChar -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqhb.f>
foreign import ccall "zlaqhb_"
   laqhb :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CChar -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqhe.f>
foreign import ccall "zlaqhe_"
   laqhe :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CChar -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqhp.f>
foreign import ccall "zlaqhp_"
   laqhp :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CChar -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqp2.f>
foreign import ccall "zlaqp2_"
   laqp2 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqps.f>
foreign import ccall "zlaqps_"
   laqps :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqr0.f>
foreign import ccall "zlaqr0_"
   laqr0 :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqr1.f>
foreign import ccall "zlaqr1_"
   laqr1 :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqr2.f>
foreign import ccall "zlaqr2_"
   laqr2 :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqr3.f>
foreign import ccall "zlaqr3_"
   laqr3 :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqr4.f>
foreign import ccall "zlaqr4_"
   laqr4 :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqr5.f>
foreign import ccall "zlaqr5_"
   laqr5 :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqsb.f>
foreign import ccall "zlaqsb_"
   laqsb :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CChar -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqsp.f>
foreign import ccall "zlaqsp_"
   laqsp :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CChar -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqsy.f>
foreign import ccall "zlaqsy_"
   laqsy :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CChar -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlar1v.f>
foreign import ccall "zlar1v_"
   lar1v :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Bool -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlar2v.f>
foreign import ccall "zlar2v_"
   lar2v :: Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarcm.f>
foreign import ccall "zlarcm_"
   larcm :: Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarf.f>
foreign import ccall "zlarf_"
   larf :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarfb.f>
foreign import ccall "zlarfb_"
   larfb :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarfg.f>
foreign import ccall "zlarfg_"
   larfg :: Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarfgp.f>
foreign import ccall "zlarfgp_"
   larfgp :: Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarft.f>
foreign import ccall "zlarft_"
   larft :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarfx.f>
foreign import ccall "zlarfx_"
   larfx :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlargv.f>
foreign import ccall "zlargv_"
   largv :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarnv.f>
foreign import ccall "zlarnv_"
   larnv :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarrv.f>
foreign import ccall "zlarrv_"
   larrv :: Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlartg.f>
foreign import ccall "zlartg_"
   lartg :: Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlartv.f>
foreign import ccall "zlartv_"
   lartv :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarz.f>
foreign import ccall "zlarz_"
   larz :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarzb.f>
foreign import ccall "zlarzb_"
   larzb :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarzt.f>
foreign import ccall "zlarzt_"
   larzt :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlascl.f>
foreign import ccall "zlascl_"
   lascl :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaset.f>
foreign import ccall "zlaset_"
   laset :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlasr.f>
foreign import ccall "zlasr_"
   lasr :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlassq.f>
foreign import ccall "zlassq_"
   lassq :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaswp.f>
foreign import ccall "zlaswp_"
   laswp :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlasyf.f>
foreign import ccall "zlasyf_"
   lasyf :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlat2c.f>
foreign import ccall "zlat2c_"
   lat2c :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Float) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlatbs.f>
foreign import ccall "zlatbs_"
   latbs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlatdf.f>
foreign import ccall "zlatdf_"
   latdf :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlatps.f>
foreign import ccall "zlatps_"
   latps :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlatrd.f>
foreign import ccall "zlatrd_"
   latrd :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlatrs.f>
foreign import ccall "zlatrs_"
   latrs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlatrz.f>
foreign import ccall "zlatrz_"
   latrz :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlauu2.f>
foreign import ccall "zlauu2_"
   lauu2 :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlauum.f>
foreign import ccall "zlauum_"
   lauum :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpbcon.f>
foreign import ccall "zpbcon_"
   pbcon :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpbequ.f>
foreign import ccall "zpbequ_"
   pbequ :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpbrfs.f>
foreign import ccall "zpbrfs_"
   pbrfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpbstf.f>
foreign import ccall "zpbstf_"
   pbstf :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpbsv.f>
foreign import ccall "zpbsv_"
   pbsv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpbsvx.f>
foreign import ccall "zpbsvx_"
   pbsvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CChar -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpbtf2.f>
foreign import ccall "zpbtf2_"
   pbtf2 :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpbtrf.f>
foreign import ccall "zpbtrf_"
   pbtrf :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpbtrs.f>
foreign import ccall "zpbtrs_"
   pbtrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpftrf.f>
foreign import ccall "zpftrf_"
   pftrf :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpftri.f>
foreign import ccall "zpftri_"
   pftri :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpftrs.f>
foreign import ccall "zpftrs_"
   pftrs :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpocon.f>
foreign import ccall "zpocon_"
   pocon :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpoequ.f>
foreign import ccall "zpoequ_"
   poequ :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpoequb.f>
foreign import ccall "zpoequb_"
   poequb :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zporfs.f>
foreign import ccall "zporfs_"
   porfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zposv.f>
foreign import ccall "zposv_"
   posv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zposvx.f>
foreign import ccall "zposvx_"
   posvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CChar -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpotf2.f>
foreign import ccall "zpotf2_"
   potf2 :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpotrf.f>
foreign import ccall "zpotrf_"
   potrf :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpotri.f>
foreign import ccall "zpotri_"
   potri :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpotrs.f>
foreign import ccall "zpotrs_"
   potrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zppcon.f>
foreign import ccall "zppcon_"
   ppcon :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zppequ.f>
foreign import ccall "zppequ_"
   ppequ :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpprfs.f>
foreign import ccall "zpprfs_"
   pprfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zppsv.f>
foreign import ccall "zppsv_"
   ppsv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zppsvx.f>
foreign import ccall "zppsvx_"
   ppsvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CChar -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpptrf.f>
foreign import ccall "zpptrf_"
   pptrf :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpptri.f>
foreign import ccall "zpptri_"
   pptri :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpptrs.f>
foreign import ccall "zpptrs_"
   pptrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpstf2.f>
foreign import ccall "zpstf2_"
   pstf2 :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpstrf.f>
foreign import ccall "zpstrf_"
   pstrf :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zptcon.f>
foreign import ccall "zptcon_"
   ptcon :: Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpteqr.f>
foreign import ccall "zpteqr_"
   pteqr :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zptrfs.f>
foreign import ccall "zptrfs_"
   ptrfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zptsv.f>
foreign import ccall "zptsv_"
   ptsv :: Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zptsvx.f>
foreign import ccall "zptsvx_"
   ptsvx :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpttrf.f>
foreign import ccall "zpttrf_"
   pttrf :: Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpttrs.f>
foreign import ccall "zpttrs_"
   pttrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zptts2.f>
foreign import ccall "zptts2_"
   ptts2 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zrot.f>
foreign import ccall "zrot_"
   rot :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zdrscl.f>
foreign import ccall "zdrscl_"
   rscl :: Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zspcon.f>
foreign import ccall "zspcon_"
   spcon :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zspmv.f>
foreign import ccall "zspmv_"
   spmv :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zspr.f>
foreign import ccall "zspr_"
   spr :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsprfs.f>
foreign import ccall "zsprfs_"
   sprfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zspsv.f>
foreign import ccall "zspsv_"
   spsv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zspsvx.f>
foreign import ccall "zspsvx_"
   spsvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsptrf.f>
foreign import ccall "zsptrf_"
   sptrf :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsptri.f>
foreign import ccall "zsptri_"
   sptri :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsptrs.f>
foreign import ccall "zsptrs_"
   sptrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zstedc.f>
foreign import ccall "zstedc_"
   stedc :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zstegr.f>
foreign import ccall "zstegr_"
   stegr :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zstein.f>
foreign import ccall "zstein_"
   stein :: Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zstemr.f>
foreign import ccall "zstemr_"
   stemr :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Bool -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsteqr.f>
foreign import ccall "zsteqr_"
   steqr :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dzsum1.f>
foreign import ccall "dzsum1_"
   sum1 :: Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsycon.f>
foreign import ccall "zsycon_"
   sycon :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsyconv.f>
foreign import ccall "zsyconv_"
   syconv :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsyequb.f>
foreign import ccall "zsyequb_"
   syequb :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsymv.f>
foreign import ccall "zsymv_"
   symv :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsyr.f>
foreign import ccall "zsyr_"
   syr :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsyrfs.f>
foreign import ccall "zsyrfs_"
   syrfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsysv.f>
foreign import ccall "zsysv_"
   sysv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsysvx.f>
foreign import ccall "zsysvx_"
   sysvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsyswapr.f>
foreign import ccall "zsyswapr_"
   syswapr :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsytf2.f>
foreign import ccall "zsytf2_"
   sytf2 :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsytrf.f>
foreign import ccall "zsytrf_"
   sytrf :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsytri.f>
foreign import ccall "zsytri_"
   sytri :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsytri2.f>
foreign import ccall "zsytri2_"
   sytri2 :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsytri2x.f>
foreign import ccall "zsytri2x_"
   sytri2x :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsytrs.f>
foreign import ccall "zsytrs_"
   sytrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsytrs2.f>
foreign import ccall "zsytrs2_"
   sytrs2 :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztbcon.f>
foreign import ccall "ztbcon_"
   tbcon :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztbrfs.f>
foreign import ccall "ztbrfs_"
   tbrfs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztbtrs.f>
foreign import ccall "ztbtrs_"
   tbtrs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztfsm.f>
foreign import ccall "ztfsm_"
   tfsm :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztftri.f>
foreign import ccall "ztftri_"
   tftri :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztfttp.f>
foreign import ccall "ztfttp_"
   tfttp :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztfttr.f>
foreign import ccall "ztfttr_"
   tfttr :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztgevc.f>
foreign import ccall "ztgevc_"
   tgevc :: Ptr CChar -> Ptr CChar -> Ptr Bool -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztgex2.f>
foreign import ccall "ztgex2_"
   tgex2 :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztgexc.f>
foreign import ccall "ztgexc_"
   tgexc :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztgsen.f>
foreign import ccall "ztgsen_"
   tgsen :: Ptr CInt -> Ptr Bool -> Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztgsja.f>
foreign import ccall "ztgsja_"
   tgsja :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztgsna.f>
foreign import ccall "ztgsna_"
   tgsna :: Ptr CChar -> Ptr CChar -> Ptr Bool -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztgsy2.f>
foreign import ccall "ztgsy2_"
   tgsy2 :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztgsyl.f>
foreign import ccall "ztgsyl_"
   tgsyl :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztpcon.f>
foreign import ccall "ztpcon_"
   tpcon :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztprfs.f>
foreign import ccall "ztprfs_"
   tprfs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztptri.f>
foreign import ccall "ztptri_"
   tptri :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztptrs.f>
foreign import ccall "ztptrs_"
   tptrs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztpttf.f>
foreign import ccall "ztpttf_"
   tpttf :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztpttr.f>
foreign import ccall "ztpttr_"
   tpttr :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztrcon.f>
foreign import ccall "ztrcon_"
   trcon :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztrevc.f>
foreign import ccall "ztrevc_"
   trevc :: Ptr CChar -> Ptr CChar -> Ptr Bool -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztrexc.f>
foreign import ccall "ztrexc_"
   trexc :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztrrfs.f>
foreign import ccall "ztrrfs_"
   trrfs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztrsen.f>
foreign import ccall "ztrsen_"
   trsen :: Ptr CChar -> Ptr CChar -> Ptr Bool -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztrsna.f>
foreign import ccall "ztrsna_"
   trsna :: Ptr CChar -> Ptr CChar -> Ptr Bool -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztrsyl.f>
foreign import ccall "ztrsyl_"
   trsyl :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztrti2.f>
foreign import ccall "ztrti2_"
   trti2 :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztrtri.f>
foreign import ccall "ztrtri_"
   trtri :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztrtrs.f>
foreign import ccall "ztrtrs_"
   trtrs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztrttf.f>
foreign import ccall "ztrttf_"
   trttf :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztrttp.f>
foreign import ccall "ztrttp_"
   trttp :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztzrzf.f>
foreign import ccall "ztzrzf_"
   tzrzf :: Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunbdb.f>
foreign import ccall "zunbdb_"
   unbdb :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zuncsd.f>
foreign import ccall "zuncsd_"
   uncsd :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zung2l.f>
foreign import ccall "zung2l_"
   ung2l :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zung2r.f>
foreign import ccall "zung2r_"
   ung2r :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zungbr.f>
foreign import ccall "zungbr_"
   ungbr :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunghr.f>
foreign import ccall "zunghr_"
   unghr :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zungl2.f>
foreign import ccall "zungl2_"
   ungl2 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunglq.f>
foreign import ccall "zunglq_"
   unglq :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zungql.f>
foreign import ccall "zungql_"
   ungql :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zungqr.f>
foreign import ccall "zungqr_"
   ungqr :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zungr2.f>
foreign import ccall "zungr2_"
   ungr2 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zungrq.f>
foreign import ccall "zungrq_"
   ungrq :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zungtr.f>
foreign import ccall "zungtr_"
   ungtr :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunm2l.f>
foreign import ccall "zunm2l_"
   unm2l :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunm2r.f>
foreign import ccall "zunm2r_"
   unm2r :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmbr.f>
foreign import ccall "zunmbr_"
   unmbr :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmhr.f>
foreign import ccall "zunmhr_"
   unmhr :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunml2.f>
foreign import ccall "zunml2_"
   unml2 :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmlq.f>
foreign import ccall "zunmlq_"
   unmlq :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmql.f>
foreign import ccall "zunmql_"
   unmql :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmqr.f>
foreign import ccall "zunmqr_"
   unmqr :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmr2.f>
foreign import ccall "zunmr2_"
   unmr2 :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmr3.f>
foreign import ccall "zunmr3_"
   unmr3 :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmrq.f>
foreign import ccall "zunmrq_"
   unmrq :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmrz.f>
foreign import ccall "zunmrz_"
   unmrz :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmtr.f>
foreign import ccall "zunmtr_"
   unmtr :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zupgtr.f>
foreign import ccall "zupgtr_"
   upgtr :: Ptr CChar -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zupmtr.f>
foreign import ccall "zupmtr_"
   upmtr :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr (Complex Double) -> Ptr CInt -> Ptr (Complex Double) -> Ptr CInt -> IO ()