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

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


-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dbbcsd.f>
foreign import ccall "dbbcsd_"
   bbcsd :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr 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/dbdsdc.f>
foreign import ccall "dbdsdc_"
   bdsdc :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ddisna.f>
foreign import ccall "ddisna_"
   disna :: Ptr CChar -> 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/dgbbrd.f>
foreign import ccall "dgbbrd_"
   gbbrd :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgbcon.f>
foreign import ccall "dgbcon_"
   gbcon :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> 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/dgbequ.f>
foreign import ccall "dgbequ_"
   gbequ :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr 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/dgbequb.f>
foreign import ccall "dgbequb_"
   gbequb :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr 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/dgbrfs.f>
foreign import ccall "dgbrfs_"
   gbrfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dgbsv.f>
foreign import ccall "dgbsv_"
   gbsv :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr 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/dgbsvx.f>
foreign import ccall "dgbsvx_"
   gbsvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CChar -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> 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/dgbtf2.f>
foreign import ccall "dgbtf2_"
   gbtf2 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> 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/dgbtrf.f>
foreign import ccall "dgbtrf_"
   gbtrf :: Ptr CInt -> Ptr CInt -> Ptr CInt -> 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/dgbtrs.f>
foreign import ccall "dgbtrs_"
   gbtrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr 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/dgebak.f>
foreign import ccall "dgebak_"
   gebak :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgebal.f>
foreign import ccall "dgebal_"
   gebal :: Ptr CChar -> Ptr CInt -> Ptr 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/dgebd2.f>
foreign import ccall "dgebd2_"
   gebd2 :: Ptr CInt -> Ptr CInt -> Ptr 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/dgebrd.f>
foreign import ccall "dgebrd_"
   gebrd :: Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dgecon.f>
foreign import ccall "dgecon_"
   gecon :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dgeequ.f>
foreign import ccall "dgeequ_"
   geequ :: Ptr CInt -> Ptr CInt -> Ptr 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/dgeequb.f>
foreign import ccall "dgeequb_"
   geequb :: Ptr CInt -> Ptr CInt -> Ptr 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/dgees.f>
foreign import ccall "dgees_"
   gees :: Ptr CChar -> Ptr CChar -> FunPtr (Ptr Double -> Ptr Double -> IO Bool) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr 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/dgeesx.f>
foreign import ccall "dgeesx_"
   geesx :: Ptr CChar -> Ptr CChar -> FunPtr (Ptr Double -> Ptr Double -> IO Bool) -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Bool -> Ptr CInt -> IO ()

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

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

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgejsv.f>
foreign import ccall "dgejsv_"
   gejsv :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr 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/dgelq2.f>
foreign import ccall "dgelq2_"
   gelq2 :: Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgelsd.f>
foreign import ccall "dgelsd_"
   gelsd :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr 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/dgelss.f>
foreign import ccall "dgelss_"
   gelss :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

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

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

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

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

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

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

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgerfs.f>
foreign import ccall "dgerfs_"
   gerfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dgerq2.f>
foreign import ccall "dgerq2_"
   gerq2 :: Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgesdd.f>
foreign import ccall "dgesdd_"
   gesdd :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr 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/dgesv.f>
foreign import ccall "dgesv_"
   gesv :: Ptr CInt -> Ptr CInt -> Ptr 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/dgesvd.f>
foreign import ccall "dgesvd_"
   gesvd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgesvx.f>
foreign import ccall "dgesvx_"
   gesvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CChar -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> 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/dgetc2.f>
foreign import ccall "dgetc2_"
   getc2 :: 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/dgetf2.f>
foreign import ccall "dgetf2_"
   getf2 :: Ptr CInt -> 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/dgetrf.f>
foreign import ccall "dgetrf_"
   getrf :: Ptr CInt -> 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/dgetri.f>
foreign import ccall "dgetri_"
   getri :: Ptr CInt -> Ptr 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/dgetrs.f>
foreign import ccall "dgetrs_"
   getrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr 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/dggbak.f>
foreign import ccall "dggbak_"
   ggbak :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dggbal.f>
foreign import ccall "dggbal_"
   ggbal :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr 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/dgges.f>
foreign import ccall "dgges_"
   gges :: Ptr CChar -> Ptr CChar -> Ptr CChar -> FunPtr (Ptr Double -> Ptr Double -> Ptr Double -> IO Bool) -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr 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/dggesx.f>
foreign import ccall "dggesx_"
   ggesx :: Ptr CChar -> Ptr CChar -> Ptr CChar -> FunPtr (Ptr Double -> Ptr Double -> Ptr Double -> IO Bool) -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Bool -> Ptr CInt -> IO ()

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dggevx.f>
foreign import ccall "dggevx_"
   ggevx :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> 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/dggglm.f>
foreign import ccall "dggglm_"
   ggglm :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> 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/dgghrd.f>
foreign import ccall "dgghrd_"
   gghrd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgglse.f>
foreign import ccall "dgglse_"
   gglse :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> 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/dggqrf.f>
foreign import ccall "dggqrf_"
   ggqrf :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

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

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgtcon.f>
foreign import ccall "dgtcon_"
   gtcon :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> 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/dgtrfs.f>
foreign import ccall "dgtrfs_"
   gtrfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dgtsv.f>
foreign import ccall "dgtsv_"
   gtsv :: 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/dgtsvx.f>
foreign import ccall "dgtsvx_"
   gtsvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> 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/dgttrf.f>
foreign import ccall "dgttrf_"
   gttrf :: 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/dgttrs.f>
foreign import ccall "dgttrs_"
   gttrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsbevd.f>
foreign import ccall "dsbevd_"
   sbevd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr 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/dsbevx.f>
foreign import ccall "dsbevx_"
   sbevx :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr 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/dsbgst.f>
foreign import ccall "dsbgst_"
   sbgst :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsbgvd.f>
foreign import ccall "dsbgvd_"
   sbgvd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr 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/dsbgvx.f>
foreign import ccall "dsbgvx_"
   sbgvx :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr 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/dsbtrd.f>
foreign import ccall "dsbtrd_"
   sbtrd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsyevd.f>
foreign import ccall "dsyevd_"
   syevd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> 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/dsyevr.f>
foreign import ccall "dsyevr_"
   syevr :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr 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/dsyevx.f>
foreign import ccall "dsyevx_"
   syevx :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr 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/dsygs2.f>
foreign import ccall "dsygs2_"
   sygs2 :: Ptr CInt -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsygvd.f>
foreign import ccall "dsygvd_"
   sygvd :: Ptr CInt -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> 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/dsygvx.f>
foreign import ccall "dsygvx_"
   sygvx :: Ptr CInt -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr 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/dsfrk.f>
foreign import ccall "dsfrk_"
   sfrk :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dspevd.f>
foreign import ccall "dspevd_"
   spevd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr 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/dspevx.f>
foreign import ccall "dspevx_"
   spevx :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr 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/dspgst.f>
foreign import ccall "dspgst_"
   spgst :: Ptr CInt -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dspgvd.f>
foreign import ccall "dspgvd_"
   spgvd :: Ptr CInt -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr 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/dspgvx.f>
foreign import ccall "dspgvx_"
   spgvx :: Ptr CInt -> Ptr CChar -> 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 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/dsptrd.f>
foreign import ccall "dsptrd_"
   sptrd :: Ptr CChar -> Ptr CInt -> 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/dhsein.f>
foreign import ccall "dhsein_"
   hsein :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr Bool -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> 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/dhseqr.f>
foreign import ccall "dhseqr_"
   hseqr :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/disnan.f>
foreign import ccall "disnan_"
   isnan :: Ptr Double -> IO Bool

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

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

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

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

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

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaebz.f>
foreign import ccall "dlaebz_"
   laebz :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr 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/dlaed0.f>
foreign import ccall "dlaed0_"
   laed0 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaed2.f>
foreign import ccall "dlaed2_"
   laed2 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr 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/dlaed3.f>
foreign import ccall "dlaed3_"
   laed3 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> 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/dlaed4.f>
foreign import ccall "dlaed4_"
   laed4 :: Ptr CInt -> 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/dlaed5.f>
foreign import ccall "dlaed5_"
   laed5 :: Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaed6.f>
foreign import ccall "dlaed6_"
   laed6 :: Ptr CInt -> Ptr Bool -> 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/dlaed7.f>
foreign import ccall "dlaed7_"
   laed7 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaed8.f>
foreign import ccall "dlaed8_"
   laed8 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> 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/dlaed9.f>
foreign import ccall "dlaed9_"
   laed9 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> 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/dlaeda.f>
foreign import ccall "dlaeda_"
   laeda :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaein.f>
foreign import ccall "dlaein_"
   laein :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> 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/dlaev2.f>
foreign import ccall "dlaev2_"
   laev2 :: Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaexc.f>
foreign import ccall "dlaexc_"
   laexc :: Ptr Bool -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> 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/dlag2.f>
foreign import ccall "dlag2_"
   lag2 :: Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlagtf.f>
foreign import ccall "dlagtf_"
   lagtf :: Ptr CInt -> 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/dlagtm.f>
foreign import ccall "dlagtm_"
   lagtm :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlahqr.f>
foreign import ccall "dlahqr_"
   lahqr :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr 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/dlahr2.f>
foreign import ccall "dlahr2_"
   lahr2 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaisnan.f>
foreign import ccall "dlaisnan_"
   laisnan :: Ptr Double -> Ptr Double -> IO Bool

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlals0.f>
foreign import ccall "dlals0_"
   lals0 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr 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/dlalsa.f>
foreign import ccall "dlalsa_"
   lalsa :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr 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/dlalsd.f>
foreign import ccall "dlalsd_"
   lalsd :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlamrg.f>
foreign import ccall "dlamrg_"
   lamrg :: Ptr CInt -> 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/dlaneg.f>
foreign import ccall "dlaneg_"
   laneg :: Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> IO CInt

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

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

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

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlansf.f>
foreign import ccall "dlansf_"
   lansf :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> IO Double

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlanst.f>
foreign import ccall "dlanst_"
   lanst :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> IO Double

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

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

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

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

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlapmr.f>
foreign import ccall "dlapmr_"
   lapmr :: Ptr Bool -> 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/dlapmt.f>
foreign import ccall "dlapmt_"
   lapmt :: Ptr Bool -> 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/dlapy2.f>
foreign import ccall "dlapy2_"
   lapy2 :: Ptr Double -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlapy3.f>
foreign import ccall "dlapy3_"
   lapy3 :: Ptr Double -> Ptr Double -> Ptr Double -> IO Double

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaqgb.f>
foreign import ccall "dlaqgb_"
   laqgb :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr 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/dlaqge.f>
foreign import ccall "dlaqge_"
   laqge :: Ptr CInt -> Ptr CInt -> Ptr 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/dlaqp2.f>
foreign import ccall "dlaqp2_"
   laqp2 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> 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/dlaqps.f>
foreign import ccall "dlaqps_"
   laqps :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dlaqr0.f>
foreign import ccall "dlaqr0_"
   laqr0 :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

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

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

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

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaqsb.f>
foreign import ccall "dlaqsb_"
   laqsb :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr 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/dlaqsp.f>
foreign import ccall "dlaqsp_"
   laqsp :: Ptr CChar -> Ptr CInt -> 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/dlaqsy.f>
foreign import ccall "dlaqsy_"
   laqsy :: Ptr CChar -> Ptr CInt -> Ptr 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/dlaqtr.f>
foreign import ccall "dlaqtr_"
   laqtr :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr 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/dlar1v.f>
foreign import ccall "dlar1v_"
   lar1v :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr 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/dlar2v.f>
foreign import ccall "dlar2v_"
   lar2v :: Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

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

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

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

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

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

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

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

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

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlarrc.f>
foreign import ccall "dlarrc_"
   larrc :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> 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/dlarrd.f>
foreign import ccall "dlarrd_"
   larrd :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr 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/dlarre.f>
foreign import ccall "dlarre_"
   larre :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> 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/dlarrf.f>
foreign import ccall "dlarrf_"
   larrf :: Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> 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/dlarrj.f>
foreign import ccall "dlarrj_"
   larrj :: Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlarrk.f>
foreign import ccall "dlarrk_"
   larrk :: Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> 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/dlarrr.f>
foreign import ccall "dlarrr_"
   larrr :: Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlarrv.f>
foreign import ccall "dlarrv_"
   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 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/dlartg.f>
foreign import ccall "dlartg_"
   lartg :: Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> IO ()

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

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

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

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

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

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

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlascl.f>
foreign import ccall "dlascl_"
   lascl :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr 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/dlasd0.f>
foreign import ccall "dlasd0_"
   lasd0 :: Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr 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/dlasd1.f>
foreign import ccall "dlasd1_"
   lasd1 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr 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/dlasd2.f>
foreign import ccall "dlasd2_"
   lasd2 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> 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/dlasd3.f>
foreign import ccall "dlasd3_"
   lasd3 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr 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/dlasd4.f>
foreign import ccall "dlasd4_"
   lasd4 :: Ptr CInt -> Ptr CInt -> Ptr Double -> 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/dlasd5.f>
foreign import ccall "dlasd5_"
   lasd5 :: Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlasd6.f>
foreign import ccall "dlasd6_"
   lasd6 :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr 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 -> Ptr CInt -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlasda.f>
foreign import ccall "dlasda_"
   lasda :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> 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/dlasdq.f>
foreign import ccall "dlasdq_"
   lasdq :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlasdt.f>
foreign import ccall "dlasdt_"
   lasdt :: Ptr CInt -> Ptr CInt -> 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/dlaset.f>
foreign import ccall "dlaset_"
   laset :: Ptr CChar -> 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/dlasq1.f>
foreign import ccall "dlasq1_"
   lasq1 :: 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/dlasq2.f>
foreign import ccall "dlasq2_"
   lasq2 :: Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

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

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlasr.f>
foreign import ccall "dlasr_"
   lasr :: Ptr CChar -> Ptr CChar -> Ptr CChar -> 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/dlasrt.f>
foreign import ccall "dlasrt_"
   lasrt :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaswp.f>
foreign import ccall "dlaswp_"
   laswp :: Ptr CInt -> Ptr 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/dlasy2.f>
foreign import ccall "dlasy2_"
   lasy2 :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlasyf.f>
foreign import ccall "dlasyf_"
   lasyf :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr 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/dlat2s.f>
foreign import ccall "dlat2s_"
   lat2s :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Float -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlatbs.f>
foreign import ccall "dlatbs_"
   latbs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> 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/dlatdf.f>
foreign import ccall "dlatdf_"
   latdf :: Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dlatps.f>
foreign import ccall "dlatps_"
   latps :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> 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/dlatrd.f>
foreign import ccall "dlatrd_"
   latrd :: Ptr CChar -> Ptr CInt -> Ptr CInt -> 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/dlatrs.f>
foreign import ccall "dlatrs_"
   latrs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> 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/dlatrz.f>
foreign import ccall "dlatrz_"
   latrz :: Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dorbdb.f>
foreign import ccall "dorbdb_"
   orbdb :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dorcsd.f>
foreign import ccall "dorcsd_"
   orcsd :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr 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/dpbcon.f>
foreign import ccall "dpbcon_"
   pbcon :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dpbequ.f>
foreign import ccall "dpbequ_"
   pbequ :: Ptr CChar -> Ptr CInt -> Ptr CInt -> 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/dpbrfs.f>
foreign import ccall "dpbrfs_"
   pbrfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dpbstf.f>
foreign import ccall "dpbstf_"
   pbstf :: Ptr CChar -> 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/dpbsv.f>
foreign import ccall "dpbsv_"
   pbsv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dpbsvx.f>
foreign import ccall "dpbsvx_"
   pbsvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CChar -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> 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/dpbtf2.f>
foreign import ccall "dpbtf2_"
   pbtf2 :: Ptr CChar -> 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/dpbtrf.f>
foreign import ccall "dpbtrf_"
   pbtrf :: Ptr CChar -> 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/dpbtrs.f>
foreign import ccall "dpbtrs_"
   pbtrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

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

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dpocon.f>
foreign import ccall "dpocon_"
   pocon :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dpoequ.f>
foreign import ccall "dpoequ_"
   poequ :: Ptr CInt -> 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/dpoequb.f>
foreign import ccall "dpoequb_"
   poequb :: Ptr CInt -> 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/dporfs.f>
foreign import ccall "dporfs_"
   porfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dposv.f>
foreign import ccall "dposv_"
   posv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dposvx.f>
foreign import ccall "dposvx_"
   posvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CChar -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> 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/dpotf2.f>
foreign import ccall "dpotf2_"
   potf2 :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

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

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dppcon.f>
foreign import ccall "dppcon_"
   ppcon :: Ptr CChar -> 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/dppequ.f>
foreign import ccall "dppequ_"
   ppequ :: Ptr CChar -> Ptr CInt -> 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/dpprfs.f>
foreign import ccall "dpprfs_"
   pprfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dppsv.f>
foreign import ccall "dppsv_"
   ppsv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dppsvx.f>
foreign import ccall "dppsvx_"
   ppsvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CChar -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> 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/dpptrf.f>
foreign import ccall "dpptrf_"
   pptrf :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dpstf2.f>
foreign import ccall "dpstf2_"
   pstf2 :: Ptr CChar -> Ptr CInt -> Ptr 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/dpstrf.f>
foreign import ccall "dpstrf_"
   pstrf :: Ptr CChar -> Ptr CInt -> Ptr 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/dptcon.f>
foreign import ccall "dptcon_"
   ptcon :: 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/dpteqr.f>
foreign import ccall "dpteqr_"
   pteqr :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dptrfs.f>
foreign import ccall "dptrfs_"
   ptrfs :: Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> 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/dptsv.f>
foreign import ccall "dptsv_"
   ptsv :: Ptr CInt -> Ptr CInt -> 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/dptsvx.f>
foreign import ccall "dptsvx_"
   ptsvx :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dpttrf.f>
foreign import ccall "dpttrf_"
   pttrf :: Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dpttrs.f>
foreign import ccall "dpttrs_"
   pttrs :: Ptr CInt -> Ptr CInt -> 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/dptts2.f>
foreign import ccall "dptts2_"
   ptts2 :: 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/drscl.f>
foreign import ccall "drscl_"
   rscl :: Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> IO ()

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dspcon.f>
foreign import ccall "dspcon_"
   spcon :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dsposv.f>
foreign import ccall "dsposv_"
   sposv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Float -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsprfs.f>
foreign import ccall "dsprfs_"
   sprfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dspsv.f>
foreign import ccall "dspsv_"
   spsv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dspsvx.f>
foreign import ccall "dspsvx_"
   spsvx :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> 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/dsptrf.f>
foreign import ccall "dsptrf_"
   sptrf :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dstebz.f>
foreign import ccall "dstebz_"
   stebz :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr 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/dstedc.f>
foreign import ccall "dstedc_"
   stedc :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr 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/dstegr.f>
foreign import ccall "dstegr_"
   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 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/dstein.f>
foreign import ccall "dstein_"
   stein :: Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr 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/dstemr.f>
foreign import ccall "dstemr_"
   stemr :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr 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/dsteqr.f>
foreign import ccall "dsteqr_"
   steqr :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dstevd.f>
foreign import ccall "dstevd_"
   stevd :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr 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/dstevr.f>
foreign import ccall "dstevr_"
   stevr :: 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 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/dstevx.f>
foreign import ccall "dstevx_"
   stevx :: 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 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/dsycon.f>
foreign import ccall "dsycon_"
   sycon :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> 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/dsyconv.f>
foreign import ccall "dsyconv_"
   syconv :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsyequb.f>
foreign import ccall "dsyequb_"
   syequb :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dsyrfs.f>
foreign import ccall "dsyrfs_"
   syrfs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dsysv.f>
foreign import ccall "dsysv_"
   sysv :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsyswapr.f>
foreign import ccall "dsyswapr_"
   syswapr :: Ptr CChar -> 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/dsytd2.f>
foreign import ccall "dsytd2_"
   sytd2 :: Ptr CChar -> Ptr CInt -> 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/dsytf2.f>
foreign import ccall "dsytf2_"
   sytf2 :: Ptr CChar -> 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/dsytrd.f>
foreign import ccall "dsytrd_"
   sytrd :: Ptr CChar -> Ptr CInt -> Ptr Double -> 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/dsytrf.f>
foreign import ccall "dsytrf_"
   sytrf :: Ptr CChar -> Ptr CInt -> Ptr 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/dsytri.f>
foreign import ccall "dsytri_"
   sytri :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsytri2.f>
foreign import ccall "dsytri2_"
   sytri2 :: Ptr CChar -> Ptr CInt -> Ptr 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/dsytri2x.f>
foreign import ccall "dsytri2x_"
   sytri2x :: Ptr CChar -> Ptr CInt -> Ptr 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/dsytrs.f>
foreign import ccall "dsytrs_"
   sytrs :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr 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/dsytrs2.f>
foreign import ccall "dsytrs2_"
   sytrs2 :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtbrfs.f>
foreign import ccall "dtbrfs_"
   tbrfs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dtbtrs.f>
foreign import ccall "dtbtrs_"
   tbtrs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtfsm.f>
foreign import ccall "dtfsm_"
   tfsm :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CChar -> 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/dtftri.f>
foreign import ccall "dtftri_"
   tftri :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtgevc.f>
foreign import ccall "dtgevc_"
   tgevc :: Ptr CChar -> Ptr CChar -> Ptr Bool -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr 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/dtgex2.f>
foreign import ccall "dtgex2_"
   tgex2 :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> 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/dtgexc.f>
foreign import ccall "dtgexc_"
   tgexc :: Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dtgsen.f>
foreign import ccall "dtgsen_"
   tgsen :: Ptr CInt -> Ptr Bool -> Ptr Bool -> Ptr Bool -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> 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/dtgsja.f>
foreign import ccall "dtgsja_"
   tgsja :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr CInt -> IO ()

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtgsna.f>
foreign import ccall "dtgsna_"
   tgsna :: Ptr CChar -> Ptr CChar -> Ptr Bool -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> 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/dtgsy2.f>
foreign import ccall "dtgsy2_"
   tgsy2 :: Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtpcon.f>
foreign import ccall "dtpcon_"
   tpcon :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> 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/dtprfs.f>
foreign import ccall "dtprfs_"
   tprfs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dtptri.f>
foreign import ccall "dtptri_"
   tptri :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

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

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

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

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

-- | <http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtrevc.f>
foreign import ccall "dtrevc_"
   trevc :: Ptr CChar -> Ptr CChar -> Ptr Bool -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr 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/dtrexc.f>
foreign import ccall "dtrexc_"
   trexc :: Ptr CChar -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr 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/dtrrfs.f>
foreign import ccall "dtrrfs_"
   trrfs :: Ptr CChar -> Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> 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/dtrsen.f>
foreign import ccall "dtrsen_"
   trsen :: Ptr CChar -> Ptr CChar -> Ptr Bool -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> 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/dtrsna.f>
foreign import ccall "dtrsna_"
   trsna :: Ptr CChar -> Ptr CChar -> Ptr Bool -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr Double -> Ptr CInt -> 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/dtrsyl.f>
foreign import ccall "dtrsyl_"
   trsyl :: Ptr CChar -> Ptr CChar -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> Ptr Double -> Ptr CInt -> IO ()

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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