{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
module Numeric.Optimization.NLOPT.Bindings (
Algorithm(..)
, algorithm_name
, Result(..)
, isSuccess
, Opt
, create
, destroy
, copy
, srand
, srand_time
, Version(..)
, version
, get_algorithm
, get_dimension
, ScalarFunction
, VectorFunction
, PreconditionerFunction
, Output(..)
, optimize
, set_min_objective
, set_max_objective
, set_precond_min_objective
, set_precond_max_objective
, set_lower_bounds
, set_lower_bounds1
, get_lower_bounds
, set_upper_bounds
, set_upper_bounds1
, get_upper_bounds
, remove_inequality_constraints
, add_inequality_constraint
, add_precond_inequality_constraint
, add_inequality_mconstraint
, remove_equality_constraints
, add_equality_constraint
, add_precond_equality_constraint
, add_equality_mconstraint
, set_stopval
, get_stopval
, set_ftol_rel
, get_ftol_rel
, set_ftol_abs
, get_ftol_abs
, set_xtol_rel
, get_xtol_rel
, set_xtol_abs1
, set_xtol_abs
, get_xtol_abs
, set_maxeval
, get_maxeval
, set_maxtime
, get_maxtime
, force_stop
, set_force_stop
, get_force_stop
, set_local_optimizer
, set_population
, get_population
, set_vector_storage
, get_vector_storage
, set_default_initial_step
, set_initial_step
, set_initial_step1
, get_initial_step
) where
import Foreign hiding (void)
import Foreign.C.String
import Foreign.C.Types
import qualified Foreign.Concurrent as CFP
import qualified Data.Vector.Storable.Mutable as MV
import qualified Data.Vector.Storable as V
data Algorithm
= GN_DIRECT
| GN_DIRECT_L
| GN_DIRECT_L_RAND
| GN_DIRECT_NOSCAL
| GN_DIRECT_L_NOSCAL
| GN_DIRECT_L_RAND_NOSCAL
| GN_ORIG_DIRECT
| GN_ORIG_DIRECT_L
| GD_STOGO
| GD_STOGO_RAND
| LD_LBFGS_NOCEDAL
| LD_LBFGS
| LN_PRAXIS
| LD_VAR2
| LD_VAR1
| LD_TNEWTON
| LD_TNEWTON_RESTART
| LD_TNEWTON_PRECOND
| LD_TNEWTON_PRECOND_RESTART
| GN_CRS2_LM
| GN_MLSL
| GD_MLSL
| GN_MLSL_LDS
| GD_MLSL_LDS
| LD_MMA
| LN_COBYLA
| LN_NEWUOA
| LN_NEWUOA_BOUND
| LN_NELDERMEAD
| LN_SBPLX
| LN_AUGLAG
| LD_AUGLAG
| LN_AUGLAG_EQ
| LD_AUGLAG_EQ
| LN_BOBYQA
| GN_ISRES
| AUGLAG
| AUGLAG_EQ
| G_MLSL
| G_MLSL_LDS
| LD_SLSQP
| LD_CCSAQ
| GN_ESCH
deriving (Algorithm -> Algorithm -> Bool
(Algorithm -> Algorithm -> Bool)
-> (Algorithm -> Algorithm -> Bool) -> Eq Algorithm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Algorithm -> Algorithm -> Bool
== :: Algorithm -> Algorithm -> Bool
$c/= :: Algorithm -> Algorithm -> Bool
/= :: Algorithm -> Algorithm -> Bool
Eq, Int -> Algorithm -> ShowS
[Algorithm] -> ShowS
Algorithm -> String
(Int -> Algorithm -> ShowS)
-> (Algorithm -> String)
-> ([Algorithm] -> ShowS)
-> Show Algorithm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Algorithm -> ShowS
showsPrec :: Int -> Algorithm -> ShowS
$cshow :: Algorithm -> String
show :: Algorithm -> String
$cshowList :: [Algorithm] -> ShowS
showList :: [Algorithm] -> ShowS
Show, ReadPrec [Algorithm]
ReadPrec Algorithm
Int -> ReadS Algorithm
ReadS [Algorithm]
(Int -> ReadS Algorithm)
-> ReadS [Algorithm]
-> ReadPrec Algorithm
-> ReadPrec [Algorithm]
-> Read Algorithm
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Algorithm
readsPrec :: Int -> ReadS Algorithm
$creadList :: ReadS [Algorithm]
readList :: ReadS [Algorithm]
$creadPrec :: ReadPrec Algorithm
readPrec :: ReadPrec Algorithm
$creadListPrec :: ReadPrec [Algorithm]
readListPrec :: ReadPrec [Algorithm]
Read, Algorithm
Algorithm -> Algorithm -> Bounded Algorithm
forall a. a -> a -> Bounded a
$cminBound :: Algorithm
minBound :: Algorithm
$cmaxBound :: Algorithm
maxBound :: Algorithm
Bounded)
instance Enum Algorithm where
fromEnum :: Algorithm -> Int
fromEnum Algorithm
GN_DIRECT = Int
0
fromEnum Algorithm
GN_DIRECT_L = Int
1
fromEnum Algorithm
GN_DIRECT_L_RAND = Int
2
fromEnum Algorithm
GN_DIRECT_NOSCAL = Int
3
fromEnum Algorithm
GN_DIRECT_L_NOSCAL = Int
4
fromEnum Algorithm
GN_DIRECT_L_RAND_NOSCAL = Int
5
fromEnum Algorithm
GN_ORIG_DIRECT = Int
6
fromEnum Algorithm
GN_ORIG_DIRECT_L = Int
7
fromEnum Algorithm
GD_STOGO = Int
8
fromEnum Algorithm
GD_STOGO_RAND = Int
9
fromEnum Algorithm
LD_LBFGS_NOCEDAL = Int
10
fromEnum Algorithm
LD_LBFGS = Int
11
fromEnum Algorithm
LN_PRAXIS = Int
12
fromEnum Algorithm
LD_VAR2 = Int
13
fromEnum Algorithm
LD_VAR1 = Int
14
fromEnum Algorithm
LD_TNEWTON = Int
15
fromEnum Algorithm
LD_TNEWTON_RESTART = Int
16
fromEnum Algorithm
LD_TNEWTON_PRECOND = Int
17
fromEnum Algorithm
LD_TNEWTON_PRECOND_RESTART = Int
18
fromEnum Algorithm
GN_CRS2_LM = Int
19
fromEnum Algorithm
GN_MLSL = Int
20
fromEnum Algorithm
GD_MLSL = Int
21
fromEnum Algorithm
GN_MLSL_LDS = Int
22
fromEnum Algorithm
GD_MLSL_LDS = Int
23
fromEnum Algorithm
LD_MMA = Int
24
fromEnum Algorithm
LN_COBYLA = Int
25
fromEnum Algorithm
LN_NEWUOA = Int
26
fromEnum Algorithm
LN_NEWUOA_BOUND = Int
27
fromEnum Algorithm
LN_NELDERMEAD = Int
28
fromEnum Algorithm
LN_SBPLX = Int
29
fromEnum Algorithm
LN_AUGLAG = Int
30
fromEnum Algorithm
LD_AUGLAG = Int
31
fromEnum Algorithm
LN_AUGLAG_EQ = Int
32
fromEnum Algorithm
LD_AUGLAG_EQ = Int
33
fromEnum Algorithm
LN_BOBYQA = Int
34
fromEnum Algorithm
GN_ISRES = Int
35
fromEnum Algorithm
AUGLAG = Int
36
fromEnum Algorithm
AUGLAG_EQ = Int
37
fromEnum Algorithm
G_MLSL = Int
38
fromEnum Algorithm
G_MLSL_LDS = Int
39
fromEnum Algorithm
LD_SLSQP = Int
40
fromEnum Algorithm
LD_CCSAQ = Int
41
fromEnum Algorithm
GN_ESCH = Int
42
toEnum :: Int -> Algorithm
toEnum Int
0 = Algorithm
GN_DIRECT
toEnum Int
1 = Algorithm
GN_DIRECT_L
toEnum Int
2 = Algorithm
GN_DIRECT_L_RAND
toEnum Int
3 = Algorithm
GN_DIRECT_NOSCAL
toEnum Int
4 = Algorithm
GN_DIRECT_L_NOSCAL
toEnum Int
5 = Algorithm
GN_DIRECT_L_RAND_NOSCAL
toEnum Int
6 = Algorithm
GN_ORIG_DIRECT
toEnum Int
7 = Algorithm
GN_ORIG_DIRECT_L
toEnum Int
8 = Algorithm
GD_STOGO
toEnum Int
9 = Algorithm
GD_STOGO_RAND
toEnum Int
10 = Algorithm
LD_LBFGS_NOCEDAL
toEnum Int
11 = Algorithm
LD_LBFGS
toEnum Int
12 = Algorithm
LN_PRAXIS
toEnum Int
13 = Algorithm
LD_VAR2
toEnum Int
14 = Algorithm
LD_VAR1
toEnum Int
15 = Algorithm
LD_TNEWTON
toEnum Int
16 = Algorithm
LD_TNEWTON_RESTART
toEnum Int
17 = Algorithm
LD_TNEWTON_PRECOND
toEnum Int
18 = Algorithm
LD_TNEWTON_PRECOND_RESTART
toEnum Int
19 = Algorithm
GN_CRS2_LM
toEnum Int
20 = Algorithm
GN_MLSL
toEnum Int
21 = Algorithm
GD_MLSL
toEnum Int
22 = Algorithm
GN_MLSL_LDS
toEnum Int
23 = Algorithm
GD_MLSL_LDS
toEnum Int
24 = Algorithm
LD_MMA
toEnum Int
25 = Algorithm
LN_COBYLA
toEnum Int
26 = Algorithm
LN_NEWUOA
toEnum Int
27 = Algorithm
LN_NEWUOA_BOUND
toEnum Int
28 = Algorithm
LN_NELDERMEAD
toEnum Int
29 = Algorithm
LN_SBPLX
toEnum Int
30 = Algorithm
LN_AUGLAG
toEnum Int
31 = Algorithm
LD_AUGLAG
toEnum Int
32 = Algorithm
LN_AUGLAG_EQ
toEnum Int
33 = Algorithm
LD_AUGLAG_EQ
toEnum Int
34 = Algorithm
LN_BOBYQA
toEnum Int
35 = Algorithm
GN_ISRES
toEnum Int
36 = Algorithm
AUGLAG
toEnum Int
37 = Algorithm
AUGLAG_EQ
toEnum Int
38 = Algorithm
G_MLSL
toEnum Int
39 = Algorithm
G_MLSL_LDS
toEnum Int
40 = Algorithm
LD_SLSQP
toEnum Int
41 = Algorithm
LD_CCSAQ
toEnum Int
42 = Algorithm
GN_ESCH
toEnum Int
e = String -> Algorithm
forall a. HasCallStack => String -> a
error (String -> Algorithm) -> String -> Algorithm
forall a b. (a -> b) -> a -> b
$
String
"Algorithm.toEnum: invalid C value '" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
e String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"' received."
foreign import ccall "nlopt.h nlopt_algorithm_name"
nlopt_algorithm_name :: CInt -> CString
algorithm_name :: Algorithm -> IO String
algorithm_name :: Algorithm -> IO String
algorithm_name = CString -> IO String
peekCString (CString -> IO String)
-> (Algorithm -> CString) -> Algorithm -> IO String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> CString
nlopt_algorithm_name (CInt -> CString) -> (Algorithm -> CInt) -> Algorithm -> CString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Algorithm -> Int) -> Algorithm -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Algorithm -> Int
forall a. Enum a => a -> Int
fromEnum
data Result
= FAILURE
| INVALID_ARGS
| OUT_OF_MEMORY
| ROUNDOFF_LIMITED
| FORCED_STOP
| SUCCESS
| STOPVAL_REACHED
| FTOL_REACHED
| XTOL_REACHED
| MAXEVAL_REACHED
| MAXTIME_REACHED
deriving (Result -> Result -> Bool
(Result -> Result -> Bool)
-> (Result -> Result -> Bool) -> Eq Result
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Result -> Result -> Bool
== :: Result -> Result -> Bool
$c/= :: Result -> Result -> Bool
/= :: Result -> Result -> Bool
Eq, ReadPrec [Result]
ReadPrec Result
Int -> ReadS Result
ReadS [Result]
(Int -> ReadS Result)
-> ReadS [Result]
-> ReadPrec Result
-> ReadPrec [Result]
-> Read Result
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Result
readsPrec :: Int -> ReadS Result
$creadList :: ReadS [Result]
readList :: ReadS [Result]
$creadPrec :: ReadPrec Result
readPrec :: ReadPrec Result
$creadListPrec :: ReadPrec [Result]
readListPrec :: ReadPrec [Result]
Read, Int -> Result -> ShowS
[Result] -> ShowS
Result -> String
(Int -> Result -> ShowS)
-> (Result -> String) -> ([Result] -> ShowS) -> Show Result
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Result -> ShowS
showsPrec :: Int -> Result -> ShowS
$cshow :: Result -> String
show :: Result -> String
$cshowList :: [Result] -> ShowS
showList :: [Result] -> ShowS
Show, Result
Result -> Result -> Bounded Result
forall a. a -> a -> Bounded a
$cminBound :: Result
minBound :: Result
$cmaxBound :: Result
maxBound :: Result
Bounded)
instance Enum Result where
fromEnum :: Result -> Int
fromEnum Result
FAILURE = -Int
1
fromEnum Result
INVALID_ARGS = -Int
2
fromEnum Result
OUT_OF_MEMORY = -Int
3
fromEnum Result
ROUNDOFF_LIMITED = -Int
4
fromEnum Result
FORCED_STOP = -Int
5
fromEnum Result
SUCCESS = Int
1
fromEnum Result
STOPVAL_REACHED = Int
2
fromEnum Result
FTOL_REACHED = Int
3
fromEnum Result
XTOL_REACHED = Int
4
fromEnum Result
MAXEVAL_REACHED = Int
5
fromEnum Result
MAXTIME_REACHED = Int
6
toEnum :: Int -> Result
toEnum (-1) = Result
FAILURE
toEnum (-2) = Result
INVALID_ARGS
toEnum (-3) = Result
OUT_OF_MEMORY
toEnum (-4) = Result
ROUNDOFF_LIMITED
toEnum (-5) = Result
FORCED_STOP
toEnum Int
1 = Result
SUCCESS
toEnum Int
2 = Result
STOPVAL_REACHED
toEnum Int
3 = Result
FTOL_REACHED
toEnum Int
4 = Result
XTOL_REACHED
toEnum Int
5 = Result
MAXEVAL_REACHED
toEnum Int
6 = Result
MAXTIME_REACHED
toEnum Int
e = String -> Result
forall a. HasCallStack => String -> a
error (String -> Result) -> String -> Result
forall a b. (a -> b) -> a -> b
$
String
"Result.toEnum: invalid C value '" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
e String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"' received."
isSuccess :: Result -> Bool
isSuccess :: Result -> Bool
isSuccess Result
SUCCESS = Bool
True
isSuccess Result
STOPVAL_REACHED = Bool
True
isSuccess Result
FTOL_REACHED = Bool
True
isSuccess Result
XTOL_REACHED = Bool
True
isSuccess Result
MAXEVAL_REACHED = Bool
True
isSuccess Result
MAXTIME_REACHED = Bool
True
isSuccess Result
_ = Bool
False
parseEnum :: (Integral a, Enum b) => a -> b
parseEnum :: forall a b. (Integral a, Enum b) => a -> b
parseEnum = Int -> b
forall a. Enum a => Int -> a
toEnum (Int -> b) -> (a -> Int) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
type NloptOpt = Ptr ()
newtype Opt = Opt { Opt -> ForeignPtr ()
pointerFromOpt :: ForeignPtr () }
withOpt :: Opt -> (NloptOpt -> IO a) -> IO a
withOpt :: forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt (Opt ForeignPtr ()
p) NloptOpt -> IO a
f = do
ret <- ForeignPtr () -> (NloptOpt -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr ()
p NloptOpt -> IO a
f
touchForeignPtr p
return ret
useOpt :: (NloptOpt -> IO a) -> Opt -> IO a
useOpt :: forall a. (NloptOpt -> IO a) -> Opt -> IO a
useOpt = (Opt -> (NloptOpt -> IO a) -> IO a)
-> (NloptOpt -> IO a) -> Opt -> IO a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Opt -> (NloptOpt -> IO a) -> IO a
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt
addFunPtrFinalizer :: Opt -> FunPtr a -> IO ()
addFunPtrFinalizer :: forall a. Opt -> FunPtr a -> IO ()
addFunPtrFinalizer (Opt ForeignPtr ()
p) FunPtr a
funptr =
ForeignPtr () -> IO () -> IO ()
forall a. ForeignPtr a -> IO () -> IO ()
CFP.addForeignPtrFinalizer ForeignPtr ()
p (FunPtr a -> IO ()
forall a. FunPtr a -> IO ()
freeHaskellFunPtr FunPtr a
funptr)
foreign import ccall "nlopt.h nlopt_create"
nlopt_create :: CInt -> CUInt -> IO (NloptOpt)
create :: Algorithm
-> Word
-> IO (Maybe Opt)
create :: Algorithm -> Word -> IO (Maybe Opt)
create Algorithm
alg Word
dimension = do
outp <- CInt -> CUInt -> IO NloptOpt
nlopt_create (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ Algorithm -> Int
forall a. Enum a => a -> Int
fromEnum Algorithm
alg) (Word -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
dimension)
if (outp == nullPtr)
then return Nothing
else Just . Opt <$> CFP.newForeignPtr outp (nlopt_destroy outp)
foreign import ccall "nlopt.h nlopt_destroy"
nlopt_destroy :: NloptOpt -> IO ()
destroy :: Opt -> IO ()
destroy :: Opt -> IO ()
destroy = ForeignPtr () -> IO ()
forall a. ForeignPtr a -> IO ()
finalizeForeignPtr (ForeignPtr () -> IO ()) -> (Opt -> ForeignPtr ()) -> Opt -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Opt -> ForeignPtr ()
pointerFromOpt
foreign import ccall "nlopt.h nlopt_copy"
nlopt_copy :: NloptOpt -> IO (NloptOpt)
copy :: Opt -> IO Opt
copy :: Opt -> IO Opt
copy = (NloptOpt -> IO Opt) -> Opt -> IO Opt
forall a. (NloptOpt -> IO a) -> Opt -> IO a
useOpt ((NloptOpt -> IO Opt) -> Opt -> IO Opt)
-> (NloptOpt -> IO Opt) -> Opt -> IO Opt
forall a b. (a -> b) -> a -> b
$ \NloptOpt
inp -> do
outp <- NloptOpt -> IO NloptOpt
nlopt_copy NloptOpt
inp
Opt <$> CFP.newForeignPtr outp (nlopt_destroy outp)
foreign import ccall "nlopt.h nlopt_srand"
nlopt_srand :: CUInt -> IO ()
srand :: Integral a => a -> IO ()
srand :: forall a. Integral a => a -> IO ()
srand = CUInt -> IO ()
nlopt_srand (CUInt -> IO ()) -> (a -> CUInt) -> a -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral
foreign import ccall "nlopt.h nlopt_srand_time"
nlopt_srand_time :: IO ()
srand_time :: IO ()
srand_time :: IO ()
srand_time = IO ()
nlopt_srand_time
foreign import ccall "nlopt.h nlopt_version"
nlopt_version :: Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()
data Version = Version
{ Version -> Int
major :: Int
, Version -> Int
minor :: Int
, Version -> Int
bugfix :: Int
} deriving (Version -> Version -> Bool
(Version -> Version -> Bool)
-> (Version -> Version -> Bool) -> Eq Version
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Version -> Version -> Bool
== :: Version -> Version -> Bool
$c/= :: Version -> Version -> Bool
/= :: Version -> Version -> Bool
Eq, Eq Version
Eq Version =>
(Version -> Version -> Ordering)
-> (Version -> Version -> Bool)
-> (Version -> Version -> Bool)
-> (Version -> Version -> Bool)
-> (Version -> Version -> Bool)
-> (Version -> Version -> Version)
-> (Version -> Version -> Version)
-> Ord Version
Version -> Version -> Bool
Version -> Version -> Ordering
Version -> Version -> Version
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Version -> Version -> Ordering
compare :: Version -> Version -> Ordering
$c< :: Version -> Version -> Bool
< :: Version -> Version -> Bool
$c<= :: Version -> Version -> Bool
<= :: Version -> Version -> Bool
$c> :: Version -> Version -> Bool
> :: Version -> Version -> Bool
$c>= :: Version -> Version -> Bool
>= :: Version -> Version -> Bool
$cmax :: Version -> Version -> Version
max :: Version -> Version -> Version
$cmin :: Version -> Version -> Version
min :: Version -> Version -> Version
Ord, ReadPrec [Version]
ReadPrec Version
Int -> ReadS Version
ReadS [Version]
(Int -> ReadS Version)
-> ReadS [Version]
-> ReadPrec Version
-> ReadPrec [Version]
-> Read Version
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Version
readsPrec :: Int -> ReadS Version
$creadList :: ReadS [Version]
readList :: ReadS [Version]
$creadPrec :: ReadPrec Version
readPrec :: ReadPrec Version
$creadListPrec :: ReadPrec [Version]
readListPrec :: ReadPrec [Version]
Read, Int -> Version -> ShowS
[Version] -> ShowS
Version -> String
(Int -> Version -> ShowS)
-> (Version -> String) -> ([Version] -> ShowS) -> Show Version
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Version -> ShowS
showsPrec :: Int -> Version -> ShowS
$cshow :: Version -> String
show :: Version -> String
$cshowList :: [Version] -> ShowS
showList :: [Version] -> ShowS
Show)
version :: IO Version
version :: IO Version
version =
(Ptr CInt -> IO Version) -> IO Version
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO Version) -> IO Version)
-> (Ptr CInt -> IO Version) -> IO Version
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
majptr ->
(Ptr CInt -> IO Version) -> IO Version
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO Version) -> IO Version)
-> (Ptr CInt -> IO Version) -> IO Version
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
minptr ->
(Ptr CInt -> IO Version) -> IO Version
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO Version) -> IO Version)
-> (Ptr CInt -> IO Version) -> IO Version
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
bfptr -> do
Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()
nlopt_version Ptr CInt
majptr Ptr CInt
minptr Ptr CInt
bfptr
Int -> Int -> Int -> Version
Version (Int -> Int -> Int -> Version)
-> IO Int -> IO (Int -> Int -> Version)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO Int
forall {a} {b}. (Integral a, Storable a, Num b) => Ptr a -> IO b
pk Ptr CInt
majptr IO (Int -> Int -> Version) -> IO Int -> IO (Int -> Version)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr CInt -> IO Int
forall {a} {b}. (Integral a, Storable a, Num b) => Ptr a -> IO b
pk Ptr CInt
minptr IO (Int -> Version) -> IO Int -> IO Version
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr CInt -> IO Int
forall {a} {b}. (Integral a, Storable a, Num b) => Ptr a -> IO b
pk Ptr CInt
bfptr
where
pk :: Ptr a -> IO b
pk = (a -> b) -> IO a -> IO b
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IO a -> IO b) -> (Ptr a -> IO a) -> Ptr a -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr a -> IO a
forall a. Storable a => Ptr a -> IO a
peek
foreign import ccall "nlopt.h nlopt_get_algorithm"
nlopt_get_algorithm :: NloptOpt -> IO CInt
get_algorithm :: Opt -> IO Algorithm
get_algorithm :: Opt -> IO Algorithm
get_algorithm = (NloptOpt -> IO Algorithm) -> Opt -> IO Algorithm
forall a. (NloptOpt -> IO a) -> Opt -> IO a
useOpt ((NloptOpt -> IO Algorithm) -> Opt -> IO Algorithm)
-> (NloptOpt -> IO Algorithm) -> Opt -> IO Algorithm
forall a b. (a -> b) -> a -> b
$ (CInt -> Algorithm) -> IO CInt -> IO Algorithm
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> Algorithm
forall a b. (Integral a, Enum b) => a -> b
parseEnum (IO CInt -> IO Algorithm)
-> (NloptOpt -> IO CInt) -> NloptOpt -> IO Algorithm
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NloptOpt -> IO CInt
nlopt_get_algorithm
foreign import ccall "nlopt.h nlopt_get_dimension"
nlopt_get_dimension :: NloptOpt -> IO CUInt
get_dimension :: Opt -> IO Word
get_dimension :: Opt -> IO Word
get_dimension = (NloptOpt -> IO Word) -> Opt -> IO Word
forall a. (NloptOpt -> IO a) -> Opt -> IO a
useOpt ((NloptOpt -> IO Word) -> Opt -> IO Word)
-> (NloptOpt -> IO Word) -> Opt -> IO Word
forall a b. (a -> b) -> a -> b
$ (CUInt -> Word) -> IO CUInt -> IO Word
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CUInt -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IO CUInt -> IO Word)
-> (NloptOpt -> IO CUInt) -> NloptOpt -> IO Word
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NloptOpt -> IO CUInt
nlopt_get_dimension
asMVector :: CUInt -> Ptr CDouble -> IO (MV.IOVector Double)
asMVector :: CUInt -> Ptr CDouble -> IO (IOVector Double)
asMVector CUInt
dim Ptr CDouble
ptr =
MVector RealWorld CDouble -> IOVector Double
forall a b s.
(Storable a, Storable b) =>
MVector s a -> MVector s b
MV.unsafeCast (MVector RealWorld CDouble -> IOVector Double)
-> (ForeignPtr CDouble -> MVector RealWorld CDouble)
-> ForeignPtr CDouble
-> IOVector Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ForeignPtr CDouble -> Int -> MVector RealWorld CDouble)
-> Int -> ForeignPtr CDouble -> MVector RealWorld CDouble
forall a b c. (a -> b -> c) -> b -> a -> c
flip ForeignPtr CDouble -> Int -> MVector RealWorld CDouble
forall a s. ForeignPtr a -> Int -> MVector s a
MV.unsafeFromForeignPtr0 (CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CUInt
dim) (ForeignPtr CDouble -> IOVector Double)
-> IO (ForeignPtr CDouble) -> IO (IOVector Double)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Ptr CDouble -> IO (ForeignPtr CDouble)
forall a. Ptr a -> IO (ForeignPtr a)
newForeignPtr_ Ptr CDouble
ptr
asVector :: CUInt -> Ptr CDouble -> IO (V.Vector Double)
asVector :: CUInt -> Ptr CDouble -> IO (Vector Double)
asVector CUInt
dim Ptr CDouble
ptr =
Vector CDouble -> Vector Double
forall a b. (Storable a, Storable b) => Vector a -> Vector b
V.unsafeCast (Vector CDouble -> Vector Double)
-> (ForeignPtr CDouble -> Vector CDouble)
-> ForeignPtr CDouble
-> Vector Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ForeignPtr CDouble -> Int -> Vector CDouble)
-> Int -> ForeignPtr CDouble -> Vector CDouble
forall a b c. (a -> b -> c) -> b -> a -> c
flip ForeignPtr CDouble -> Int -> Vector CDouble
forall a. ForeignPtr a -> Int -> Vector a
V.unsafeFromForeignPtr0 (CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CUInt
dim) (ForeignPtr CDouble -> Vector Double)
-> IO (ForeignPtr CDouble) -> IO (Vector Double)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Ptr CDouble -> IO (ForeignPtr CDouble)
forall a. Ptr a -> IO (ForeignPtr a)
newForeignPtr_ Ptr CDouble
ptr
type CFunc a = CUInt -> Ptr CDouble -> Ptr CDouble -> StablePtr a -> IO CDouble
type ScalarFunction a
= V.Vector Double
-> Maybe (MV.IOVector Double)
-> a
-> IO Double
type VectorFunction a
= V.Vector Double
-> MV.IOVector Double
-> Maybe (MV.IOVector Double)
-> a
-> IO ()
type PreconditionerFunction a
= V.Vector Double
-> V.Vector Double
-> MV.IOVector Double
-> a
-> IO ()
wrapCFunction :: ScalarFunction a -> CFunc a
wrapCFunction :: forall a. ScalarFunction a -> CFunc a
wrapCFunction ScalarFunction a
cfunc CUInt
dim Ptr CDouble
stateptr Ptr CDouble
gradientptr StablePtr a
userptr = do
nloptgradient <- CUInt -> Ptr CDouble -> IO (IOVector Double)
asMVector CUInt
dim Ptr CDouble
gradientptr
statevec <- asVector dim stateptr
userdata <- deRefStablePtr userptr
let
gradptr = if Ptr CDouble
gradientptr Ptr CDouble -> Ptr CDouble -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr CDouble
forall a. Ptr a
nullPtr
then IOVector Double -> Maybe (IOVector Double)
forall a. a -> Maybe a
Just IOVector Double
nloptgradient
else Maybe (IOVector Double)
forall a. Maybe a
Nothing
realToFrac <$> cfunc statevec gradptr userdata
foreign import ccall safe "wrapper"
mkCFunction :: CFunc a -> IO (FunPtr (CFunc a))
type CMFunc a = CUInt -> Ptr CDouble -> CUInt -> Ptr CDouble
-> Ptr CDouble -> StablePtr a -> IO ()
wrapMFunction :: VectorFunction a -> CMFunc a
wrapMFunction :: forall a. VectorFunction a -> CMFunc a
wrapMFunction VectorFunction a
mfunc CUInt
constrdim Ptr CDouble
constrptr CUInt
dim Ptr CDouble
stateptr Ptr CDouble
gradientptr StablePtr a
userptr
= do
nloptgradient <- CUInt -> Ptr CDouble -> IO (IOVector Double)
asMVector (CUInt
dim CUInt -> CUInt -> CUInt
forall a. Num a => a -> a -> a
* CUInt
constrdim) Ptr CDouble
gradientptr
nloptconstraint <- asMVector constrdim constrptr
statevec <- asVector dim stateptr
userdata <- deRefStablePtr userptr
let
gradptr = if Ptr CDouble
gradientptr Ptr CDouble -> Ptr CDouble -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr CDouble
forall a. Ptr a
nullPtr
then IOVector Double -> Maybe (IOVector Double)
forall a. a -> Maybe a
Just IOVector Double
nloptgradient
else Maybe (IOVector Double)
forall a. Maybe a
Nothing
mfunc statevec nloptconstraint gradptr userdata
foreign import ccall safe "wrapper"
mkMFunction :: CMFunc a -> IO (FunPtr (CMFunc a))
type CPrecond a = CUInt -> Ptr CDouble -> Ptr CDouble
-> Ptr CDouble -> StablePtr a -> IO ()
wrapPreconditioner :: PreconditionerFunction a -> CPrecond a
wrapPreconditioner :: forall a. PreconditionerFunction a -> CPrecond a
wrapPreconditioner PreconditionerFunction a
prec CUInt
dim Ptr CDouble
stateptr Ptr CDouble
vptr Ptr CDouble
preptr StablePtr a
userptr = do
nloptpre <- CUInt -> Ptr CDouble -> IO (IOVector Double)
asMVector CUInt
dim Ptr CDouble
preptr
statevec <- asVector dim stateptr
vvec <- asVector dim vptr
userdata <- deRefStablePtr userptr
prec statevec vvec nloptpre userdata
foreign import ccall safe "wrapper"
mkPreconditionerFunction :: CPrecond a -> IO (FunPtr (CPrecond a))
addStablePtrFinalizer :: Opt -> StablePtr a -> IO ()
addStablePtrFinalizer :: forall a. Opt -> StablePtr a -> IO ()
addStablePtrFinalizer (Opt ForeignPtr ()
p) StablePtr a
sp =
ForeignPtr () -> IO () -> IO ()
forall a. ForeignPtr a -> IO () -> IO ()
CFP.addForeignPtrFinalizer ForeignPtr ()
p (StablePtr a -> IO ()
forall a. StablePtr a -> IO ()
freeStablePtr StablePtr a
sp)
getStablePtr :: Opt -> a -> IO (StablePtr a)
getStablePtr :: forall a. Opt -> a -> IO (StablePtr a)
getStablePtr Opt
opt a
a = do
aptr <- a -> IO (StablePtr a)
forall a. a -> IO (StablePtr a)
newStablePtr a
a
addStablePtrFinalizer opt aptr
return aptr
exportFunPtr :: (t1 -> IO (FunPtr a)) -> (t -> t1) -> t -> Opt -> IO (FunPtr a)
exportFunPtr :: forall t1 a t.
(t1 -> IO (FunPtr a)) -> (t -> t1) -> t -> Opt -> IO (FunPtr a)
exportFunPtr t1 -> IO (FunPtr a)
mk t -> t1
wrap t
fun Opt
opt = do
funptr <- t1 -> IO (FunPtr a)
mk (t1 -> IO (FunPtr a)) -> t1 -> IO (FunPtr a)
forall a b. (a -> b) -> a -> b
$ t -> t1
wrap t
fun
addFunPtrFinalizer opt funptr
return funptr
data Output = Output
{ Output -> Result
resultCode :: Result
, Output -> Double
resultCost :: Double
, Output -> Vector Double
resultParameters :: V.Vector Double
}
foreign import ccall "nlopt.h nlopt_optimize"
nlopt_optimize :: NloptOpt -> Ptr CDouble -> Ptr CDouble -> IO CInt
optimize :: Opt
-> V.Vector Double
-> IO Output
optimize :: Opt -> Vector Double -> IO Output
optimize Opt
optimizer Vector Double
x0 = Opt -> (NloptOpt -> IO Output) -> IO Output
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
optimizer ((NloptOpt -> IO Output) -> IO Output)
-> (NloptOpt -> IO Output) -> IO Output
forall a b. (a -> b) -> a -> b
$ \NloptOpt
opt -> do
vmut <- Vector CDouble -> IO (MVector (PrimState IO) CDouble)
forall a (m :: * -> *).
(Storable a, PrimMonad m) =>
Vector a -> m (MVector (PrimState m) a)
V.thaw (Vector CDouble -> IO (MVector (PrimState IO) CDouble))
-> Vector CDouble -> IO (MVector (PrimState IO) CDouble)
forall a b. (a -> b) -> a -> b
$ Vector Double -> Vector CDouble
forall a b. (Storable a, Storable b) => Vector a -> Vector b
V.unsafeCast Vector Double
x0
alloca $ \Ptr CDouble
costPtr -> do
result <- MVector RealWorld CDouble
-> (Ptr CDouble -> IO Result) -> IO Result
forall a b. Storable a => IOVector a -> (Ptr a -> IO b) -> IO b
MV.unsafeWith MVector RealWorld CDouble
vmut ((Ptr CDouble -> IO Result) -> IO Result)
-> (Ptr CDouble -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \Ptr CDouble
xptr ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> Ptr CDouble -> Ptr CDouble -> IO CInt
nlopt_optimize NloptOpt
opt Ptr CDouble
xptr Ptr CDouble
costPtr
outputCost <- peek . castPtr $ costPtr
iceout <- V.unsafeFreeze (MV.unsafeCast vmut)
return $ Output result outputCost iceout
foreign import ccall "nlopt.h nlopt_set_min_objective"
nlopt_set_min_objective :: NloptOpt -> FunPtr (CFunc a)
-> StablePtr a -> IO CInt
foreign import ccall "nlopt.h nlopt_set_max_objective"
nlopt_set_max_objective :: NloptOpt -> FunPtr (CFunc a)
-> StablePtr a -> IO CInt
set_min_objective :: Opt -> ScalarFunction a -> a -> IO Result
set_min_objective :: forall a. Opt -> ScalarFunction a -> a -> IO Result
set_min_objective Opt
opt ScalarFunction a
objf a
userdata = do
objfunptr <- (CFunc a -> IO (FunPtr (CFunc a)))
-> (ScalarFunction a -> CFunc a)
-> ScalarFunction a
-> Opt
-> IO (FunPtr (CFunc a))
forall t1 a t.
(t1 -> IO (FunPtr a)) -> (t -> t1) -> t -> Opt -> IO (FunPtr a)
exportFunPtr CFunc a -> IO (FunPtr (CFunc a))
forall a. CFunc a -> IO (FunPtr (CFunc a))
mkCFunction ScalarFunction a -> CFunc a
forall a. ScalarFunction a -> CFunc a
wrapCFunction ScalarFunction a
objf Opt
opt
userptr <- getStablePtr opt userdata
withOpt opt $ \NloptOpt
o ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
NloptOpt -> FunPtr (CFunc a) -> StablePtr a -> IO CInt
forall a. NloptOpt -> FunPtr (CFunc a) -> StablePtr a -> IO CInt
nlopt_set_min_objective NloptOpt
o FunPtr (CFunc a)
objfunptr StablePtr a
userptr
set_max_objective :: Opt -> ScalarFunction a -> a -> IO Result
set_max_objective :: forall a. Opt -> ScalarFunction a -> a -> IO Result
set_max_objective Opt
opt ScalarFunction a
objf a
userdata = do
objfunptr <- (CFunc a -> IO (FunPtr (CFunc a)))
-> (ScalarFunction a -> CFunc a)
-> ScalarFunction a
-> Opt
-> IO (FunPtr (CFunc a))
forall t1 a t.
(t1 -> IO (FunPtr a)) -> (t -> t1) -> t -> Opt -> IO (FunPtr a)
exportFunPtr CFunc a -> IO (FunPtr (CFunc a))
forall a. CFunc a -> IO (FunPtr (CFunc a))
mkCFunction ScalarFunction a -> CFunc a
forall a. ScalarFunction a -> CFunc a
wrapCFunction ScalarFunction a
objf Opt
opt
userptr <- getStablePtr opt userdata
withOpt opt $ \NloptOpt
o ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> FunPtr (CFunc a) -> StablePtr a -> IO CInt
forall a. NloptOpt -> FunPtr (CFunc a) -> StablePtr a -> IO CInt
nlopt_set_max_objective NloptOpt
o FunPtr (CFunc a)
objfunptr StablePtr a
userptr
foreign import ccall "nlopt.h nlopt_set_precond_min_objective"
nlopt_set_precond_min_objective :: NloptOpt
-> FunPtr (CFunc a)
-> FunPtr (CPrecond a)
-> StablePtr a
-> IO CInt
foreign import ccall "nlopt.h nlopt_set_precond_max_objective"
nlopt_set_precond_max_objective :: NloptOpt
-> FunPtr (CFunc a)
-> FunPtr (CPrecond a)
-> StablePtr a
-> IO CInt
set_precond_min_objective :: Opt
-> ScalarFunction a
-> PreconditionerFunction a
-> a
-> IO Result
set_precond_min_objective :: forall a.
Opt
-> ScalarFunction a -> PreconditionerFunction a -> a -> IO Result
set_precond_min_objective Opt
opt ScalarFunction a
objf PreconditionerFunction a
pref a
userdata = do
objfunptr <- (CFunc a -> IO (FunPtr (CFunc a)))
-> (ScalarFunction a -> CFunc a)
-> ScalarFunction a
-> Opt
-> IO (FunPtr (CFunc a))
forall t1 a t.
(t1 -> IO (FunPtr a)) -> (t -> t1) -> t -> Opt -> IO (FunPtr a)
exportFunPtr CFunc a -> IO (FunPtr (CFunc a))
forall a. CFunc a -> IO (FunPtr (CFunc a))
mkCFunction ScalarFunction a -> CFunc a
forall a. ScalarFunction a -> CFunc a
wrapCFunction ScalarFunction a
objf Opt
opt
prefunptr <- exportFunPtr mkPreconditionerFunction wrapPreconditioner pref opt
userptr <- getStablePtr opt userdata
withOpt opt $ \NloptOpt
o -> CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
NloptOpt
-> FunPtr (CFunc a)
-> FunPtr (CPrecond a)
-> StablePtr a
-> IO CInt
forall a.
NloptOpt
-> FunPtr (CFunc a)
-> FunPtr (CPrecond a)
-> StablePtr a
-> IO CInt
nlopt_set_precond_min_objective NloptOpt
o FunPtr (CFunc a)
objfunptr FunPtr (CPrecond a)
prefunptr StablePtr a
userptr
set_precond_max_objective :: Opt
-> ScalarFunction a
-> PreconditionerFunction a
-> a
-> IO Result
set_precond_max_objective :: forall a.
Opt
-> ScalarFunction a -> PreconditionerFunction a -> a -> IO Result
set_precond_max_objective Opt
opt ScalarFunction a
objf PreconditionerFunction a
pref a
userdata = do
objfunptr <- (CFunc a -> IO (FunPtr (CFunc a)))
-> (ScalarFunction a -> CFunc a)
-> ScalarFunction a
-> Opt
-> IO (FunPtr (CFunc a))
forall t1 a t.
(t1 -> IO (FunPtr a)) -> (t -> t1) -> t -> Opt -> IO (FunPtr a)
exportFunPtr CFunc a -> IO (FunPtr (CFunc a))
forall a. CFunc a -> IO (FunPtr (CFunc a))
mkCFunction ScalarFunction a -> CFunc a
forall a. ScalarFunction a -> CFunc a
wrapCFunction ScalarFunction a
objf Opt
opt
prefunptr <- exportFunPtr mkPreconditionerFunction wrapPreconditioner pref opt
userptr <- getStablePtr opt userdata
withOpt opt $ \NloptOpt
o -> CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
NloptOpt
-> FunPtr (CFunc a)
-> FunPtr (CPrecond a)
-> StablePtr a
-> IO CInt
forall a.
NloptOpt
-> FunPtr (CFunc a)
-> FunPtr (CPrecond a)
-> StablePtr a
-> IO CInt
nlopt_set_precond_max_objective NloptOpt
o FunPtr (CFunc a)
objfunptr FunPtr (CPrecond a)
prefunptr StablePtr a
userptr
foreign import ccall "nlopt.h nlopt_set_lower_bounds"
nlopt_set_lower_bounds :: NloptOpt -> Ptr CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_set_lower_bounds1"
nlopt_set_lower_bounds1 :: NloptOpt -> CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_get_lower_bounds"
nlopt_get_lower_bounds :: NloptOpt -> Ptr CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_set_upper_bounds"
nlopt_set_upper_bounds :: NloptOpt -> Ptr CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_set_upper_bounds1"
nlopt_set_upper_bounds1 :: NloptOpt -> CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_get_upper_bounds"
nlopt_get_upper_bounds :: NloptOpt -> Ptr CDouble -> IO CInt
set_lower_bounds :: Opt -> V.Vector Double -> IO Result
set_lower_bounds :: Opt -> Vector Double -> IO Result
set_lower_bounds Opt
opt Vector Double
bounds =
ForeignPtr CDouble -> (Ptr CDouble -> IO Result) -> IO Result
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ((ForeignPtr CDouble, Int) -> ForeignPtr CDouble
forall a b. (a, b) -> a
fst ((ForeignPtr CDouble, Int) -> ForeignPtr CDouble)
-> (Vector Double -> (ForeignPtr CDouble, Int))
-> Vector Double
-> ForeignPtr CDouble
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector CDouble -> (ForeignPtr CDouble, Int)
forall a. Vector a -> (ForeignPtr a, Int)
V.unsafeToForeignPtr0 (Vector CDouble -> (ForeignPtr CDouble, Int))
-> (Vector Double -> Vector CDouble)
-> Vector Double
-> (ForeignPtr CDouble, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Double -> Vector CDouble
forall a b. (Storable a, Storable b) => Vector a -> Vector b
V.unsafeCast (Vector Double -> ForeignPtr CDouble)
-> Vector Double -> ForeignPtr CDouble
forall a b. (a -> b) -> a -> b
$ Vector Double
bounds) ((Ptr CDouble -> IO Result) -> IO Result)
-> (Ptr CDouble -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$
\Ptr CDouble
bptr -> Opt -> (NloptOpt -> IO Result) -> IO Result
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
opt ((NloptOpt -> IO Result) -> IO Result)
-> (NloptOpt -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \NloptOpt
o ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> Ptr CDouble -> IO CInt
nlopt_set_lower_bounds NloptOpt
o Ptr CDouble
bptr
set_lower_bounds1 :: Opt -> Double -> IO Result
set_lower_bounds1 :: Opt -> Double -> IO Result
set_lower_bounds1 Opt
opt Double
bound =
Opt -> (NloptOpt -> IO Result) -> IO Result
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
opt ((NloptOpt -> IO Result) -> IO Result)
-> (NloptOpt -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \NloptOpt
o ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> CDouble -> IO CInt
nlopt_set_lower_bounds1 NloptOpt
o (Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
bound)
get_lower_bounds :: Opt -> IO (V.Vector Double, Result)
get_lower_bounds :: Opt -> IO (Vector Double, Result)
get_lower_bounds Opt
opt = do
v <- Opt -> IO Word
get_dimension Opt
opt IO Word -> (Word -> IO (IOVector Double)) -> IO (IOVector Double)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> IO (IOVector Double)
Int -> IO (MVector (PrimState IO) Double)
forall (m :: * -> *) a.
(PrimMonad m, Storable a) =>
Int -> m (MVector (PrimState m) a)
MV.new (Int -> IO (IOVector Double))
-> (Word -> Int) -> Word -> IO (IOVector Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
MV.unsafeWith (MV.unsafeCast v) $ \Ptr CDouble
vptr -> Opt
-> (NloptOpt -> IO (Vector Double, Result))
-> IO (Vector Double, Result)
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
opt ((NloptOpt -> IO (Vector Double, Result))
-> IO (Vector Double, Result))
-> (NloptOpt -> IO (Vector Double, Result))
-> IO (Vector Double, Result)
forall a b. (a -> b) -> a -> b
$ \NloptOpt
o -> do
result <- CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> Ptr CDouble -> IO CInt
nlopt_get_lower_bounds NloptOpt
o Ptr CDouble
vptr
retv <- V.unsafeFreeze v
return (retv, result)
set_upper_bounds :: Opt -> V.Vector Double -> IO Result
set_upper_bounds :: Opt -> Vector Double -> IO Result
set_upper_bounds Opt
opt Vector Double
bounds =
ForeignPtr CDouble -> (Ptr CDouble -> IO Result) -> IO Result
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ((ForeignPtr CDouble, Int) -> ForeignPtr CDouble
forall a b. (a, b) -> a
fst ((ForeignPtr CDouble, Int) -> ForeignPtr CDouble)
-> (Vector Double -> (ForeignPtr CDouble, Int))
-> Vector Double
-> ForeignPtr CDouble
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector CDouble -> (ForeignPtr CDouble, Int)
forall a. Vector a -> (ForeignPtr a, Int)
V.unsafeToForeignPtr0 (Vector CDouble -> (ForeignPtr CDouble, Int))
-> (Vector Double -> Vector CDouble)
-> Vector Double
-> (ForeignPtr CDouble, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Double -> Vector CDouble
forall a b. (Storable a, Storable b) => Vector a -> Vector b
V.unsafeCast (Vector Double -> ForeignPtr CDouble)
-> Vector Double -> ForeignPtr CDouble
forall a b. (a -> b) -> a -> b
$ Vector Double
bounds) ((Ptr CDouble -> IO Result) -> IO Result)
-> (Ptr CDouble -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$
\Ptr CDouble
bptr -> Opt -> (NloptOpt -> IO Result) -> IO Result
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
opt ((NloptOpt -> IO Result) -> IO Result)
-> (NloptOpt -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \NloptOpt
o ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> Ptr CDouble -> IO CInt
nlopt_set_upper_bounds NloptOpt
o Ptr CDouble
bptr
set_upper_bounds1 :: Opt -> Double -> IO Result
set_upper_bounds1 :: Opt -> Double -> IO Result
set_upper_bounds1 Opt
opt Double
bound =
Opt -> (NloptOpt -> IO Result) -> IO Result
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
opt ((NloptOpt -> IO Result) -> IO Result)
-> (NloptOpt -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \NloptOpt
o ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> CDouble -> IO CInt
nlopt_set_upper_bounds1 NloptOpt
o (Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
bound)
get_upper_bounds :: Opt -> IO (V.Vector Double, Result)
get_upper_bounds :: Opt -> IO (Vector Double, Result)
get_upper_bounds Opt
opt = do
v <- Opt -> IO Word
get_dimension Opt
opt IO Word -> (Word -> IO (IOVector Double)) -> IO (IOVector Double)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> IO (IOVector Double)
Int -> IO (MVector (PrimState IO) Double)
forall (m :: * -> *) a.
(PrimMonad m, Storable a) =>
Int -> m (MVector (PrimState m) a)
MV.new (Int -> IO (IOVector Double))
-> (Word -> Int) -> Word -> IO (IOVector Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
MV.unsafeWith (MV.unsafeCast v) $ \Ptr CDouble
vptr -> Opt
-> (NloptOpt -> IO (Vector Double, Result))
-> IO (Vector Double, Result)
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
opt ((NloptOpt -> IO (Vector Double, Result))
-> IO (Vector Double, Result))
-> (NloptOpt -> IO (Vector Double, Result))
-> IO (Vector Double, Result)
forall a b. (a -> b) -> a -> b
$ \NloptOpt
o -> do
result <- CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> Ptr CDouble -> IO CInt
nlopt_get_upper_bounds NloptOpt
o Ptr CDouble
vptr
retv <- V.unsafeFreeze v
return (retv, result)
foreign import ccall "nlopt.h nlopt_remove_inequality_constraints"
nlopt_remove_inequality_constraints :: NloptOpt -> IO CInt
foreign import ccall "nlopt.h nlopt_add_inequality_constraint"
nlopt_add_inequality_constraint :: NloptOpt -> FunPtr (CFunc a)
-> StablePtr a -> CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_add_precond_inequality_constraint"
nlopt_add_precond_inequality_constraint :: NloptOpt -> FunPtr (CFunc a)
-> FunPtr (CPrecond a) -> StablePtr a
-> CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_add_inequality_mconstraint"
nlopt_add_inequality_mconstraint :: NloptOpt -> CUInt -> FunPtr (CMFunc a)
-> StablePtr a -> CDouble -> IO CInt
remove_inequality_constraints :: Opt -> IO Result
remove_inequality_constraints :: Opt -> IO Result
remove_inequality_constraints =
(NloptOpt -> IO Result) -> Opt -> IO Result
forall a. (NloptOpt -> IO a) -> Opt -> IO a
useOpt ((NloptOpt -> IO Result) -> Opt -> IO Result)
-> (NloptOpt -> IO Result) -> Opt -> IO Result
forall a b. (a -> b) -> a -> b
$ (CInt -> Result) -> IO CInt -> IO Result
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (IO CInt -> IO Result)
-> (NloptOpt -> IO CInt) -> NloptOpt -> IO Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NloptOpt -> IO CInt
nlopt_remove_inequality_constraints
add_inequality_constraint :: Opt -> ScalarFunction a
-> a -> Double -> IO Result
add_inequality_constraint :: forall a. Opt -> ScalarFunction a -> a -> Double -> IO Result
add_inequality_constraint Opt
opt ScalarFunction a
objfun a
userdata Double
tol = do
objfunptr <- (CFunc a -> IO (FunPtr (CFunc a)))
-> (ScalarFunction a -> CFunc a)
-> ScalarFunction a
-> Opt
-> IO (FunPtr (CFunc a))
forall t1 a t.
(t1 -> IO (FunPtr a)) -> (t -> t1) -> t -> Opt -> IO (FunPtr a)
exportFunPtr CFunc a -> IO (FunPtr (CFunc a))
forall a. CFunc a -> IO (FunPtr (CFunc a))
mkCFunction ScalarFunction a -> CFunc a
forall a. ScalarFunction a -> CFunc a
wrapCFunction ScalarFunction a
objfun Opt
opt
userptr <- getStablePtr opt userdata
withOpt opt $ \NloptOpt
o ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
NloptOpt -> FunPtr (CFunc a) -> StablePtr a -> CDouble -> IO CInt
forall a.
NloptOpt -> FunPtr (CFunc a) -> StablePtr a -> CDouble -> IO CInt
nlopt_add_inequality_constraint NloptOpt
o FunPtr (CFunc a)
objfunptr StablePtr a
userptr (Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
tol)
add_precond_inequality_constraint :: Opt -> ScalarFunction a
-> PreconditionerFunction a -> a -> Double
-> IO Result
add_precond_inequality_constraint :: forall a.
Opt
-> ScalarFunction a
-> PreconditionerFunction a
-> a
-> Double
-> IO Result
add_precond_inequality_constraint Opt
opt ScalarFunction a
objfun PreconditionerFunction a
precfun a
userdata Double
tol = do
objfunptr <- (CFunc a -> IO (FunPtr (CFunc a)))
-> (ScalarFunction a -> CFunc a)
-> ScalarFunction a
-> Opt
-> IO (FunPtr (CFunc a))
forall t1 a t.
(t1 -> IO (FunPtr a)) -> (t -> t1) -> t -> Opt -> IO (FunPtr a)
exportFunPtr CFunc a -> IO (FunPtr (CFunc a))
forall a. CFunc a -> IO (FunPtr (CFunc a))
mkCFunction ScalarFunction a -> CFunc a
forall a. ScalarFunction a -> CFunc a
wrapCFunction ScalarFunction a
objfun Opt
opt
precfunptr <-
exportFunPtr mkPreconditionerFunction wrapPreconditioner precfun opt
userptr <- getStablePtr opt userdata
withOpt opt $ \NloptOpt
o ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
NloptOpt
-> FunPtr (CFunc a)
-> FunPtr (CPrecond a)
-> StablePtr a
-> CDouble
-> IO CInt
forall a.
NloptOpt
-> FunPtr (CFunc a)
-> FunPtr (CPrecond a)
-> StablePtr a
-> CDouble
-> IO CInt
nlopt_add_precond_inequality_constraint NloptOpt
o FunPtr (CFunc a)
objfunptr
FunPtr (CPrecond a)
precfunptr StablePtr a
userptr (Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
tol)
add_inequality_mconstraint :: Opt -> Word -> VectorFunction a -> a
-> Double -> IO Result
add_inequality_mconstraint :: forall a.
Opt -> Word -> VectorFunction a -> a -> Double -> IO Result
add_inequality_mconstraint Opt
opt Word
constraintsize VectorFunction a
constrfun a
userdata Double
tol = do
constrfunptr <- (CMFunc a -> IO (FunPtr (CMFunc a)))
-> (VectorFunction a -> CMFunc a)
-> VectorFunction a
-> Opt
-> IO (FunPtr (CMFunc a))
forall t1 a t.
(t1 -> IO (FunPtr a)) -> (t -> t1) -> t -> Opt -> IO (FunPtr a)
exportFunPtr CMFunc a -> IO (FunPtr (CMFunc a))
forall a. CMFunc a -> IO (FunPtr (CMFunc a))
mkMFunction VectorFunction a -> CMFunc a
forall a. VectorFunction a -> CMFunc a
wrapMFunction VectorFunction a
constrfun Opt
opt
userptr <- getStablePtr opt userdata
withOpt opt $ \NloptOpt
o ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
NloptOpt
-> CUInt -> FunPtr (CMFunc a) -> StablePtr a -> CDouble -> IO CInt
forall a.
NloptOpt
-> CUInt -> FunPtr (CMFunc a) -> StablePtr a -> CDouble -> IO CInt
nlopt_add_inequality_mconstraint NloptOpt
o (Word -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
constraintsize)
FunPtr (CMFunc a)
constrfunptr StablePtr a
userptr (Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
tol)
foreign import ccall "nlopt.h nlopt_remove_equality_constraints"
nlopt_remove_equality_constraints :: NloptOpt -> IO CInt
foreign import ccall "nlopt.h nlopt_add_equality_constraint"
nlopt_add_equality_constraint :: NloptOpt -> FunPtr (CFunc a)
-> StablePtr a -> CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_add_precond_equality_constraint"
nlopt_add_precond_equality_constraint :: NloptOpt -> FunPtr (CFunc a)
-> FunPtr (CPrecond a) -> StablePtr a
-> CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_add_equality_mconstraint"
nlopt_add_equality_mconstraint :: NloptOpt -> CUInt -> FunPtr (CMFunc a)
-> StablePtr a -> CDouble -> IO CInt
remove_equality_constraints :: Opt -> IO Result
remove_equality_constraints :: Opt -> IO Result
remove_equality_constraints =
(NloptOpt -> IO Result) -> Opt -> IO Result
forall a. (NloptOpt -> IO a) -> Opt -> IO a
useOpt ((NloptOpt -> IO Result) -> Opt -> IO Result)
-> (NloptOpt -> IO Result) -> Opt -> IO Result
forall a b. (a -> b) -> a -> b
$ (CInt -> Result) -> IO CInt -> IO Result
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (IO CInt -> IO Result)
-> (NloptOpt -> IO CInt) -> NloptOpt -> IO Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NloptOpt -> IO CInt
nlopt_remove_equality_constraints
add_equality_constraint :: Opt -> ScalarFunction a
-> a -> Double -> IO Result
add_equality_constraint :: forall a. Opt -> ScalarFunction a -> a -> Double -> IO Result
add_equality_constraint Opt
opt ScalarFunction a
objfun a
userdata Double
tol = do
objfunptr <- (CFunc a -> IO (FunPtr (CFunc a)))
-> (ScalarFunction a -> CFunc a)
-> ScalarFunction a
-> Opt
-> IO (FunPtr (CFunc a))
forall t1 a t.
(t1 -> IO (FunPtr a)) -> (t -> t1) -> t -> Opt -> IO (FunPtr a)
exportFunPtr CFunc a -> IO (FunPtr (CFunc a))
forall a. CFunc a -> IO (FunPtr (CFunc a))
mkCFunction ScalarFunction a -> CFunc a
forall a. ScalarFunction a -> CFunc a
wrapCFunction ScalarFunction a
objfun Opt
opt
userptr <- getStablePtr opt userdata
withOpt opt $ \NloptOpt
o ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
NloptOpt -> FunPtr (CFunc a) -> StablePtr a -> CDouble -> IO CInt
forall a.
NloptOpt -> FunPtr (CFunc a) -> StablePtr a -> CDouble -> IO CInt
nlopt_add_equality_constraint NloptOpt
o FunPtr (CFunc a)
objfunptr StablePtr a
userptr (Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
tol)
add_precond_equality_constraint :: Opt -> ScalarFunction a
-> PreconditionerFunction a -> a -> Double
-> IO Result
add_precond_equality_constraint :: forall a.
Opt
-> ScalarFunction a
-> PreconditionerFunction a
-> a
-> Double
-> IO Result
add_precond_equality_constraint Opt
opt ScalarFunction a
objfun PreconditionerFunction a
precfun a
userdata Double
tol = do
objfunptr <- (CFunc a -> IO (FunPtr (CFunc a)))
-> (ScalarFunction a -> CFunc a)
-> ScalarFunction a
-> Opt
-> IO (FunPtr (CFunc a))
forall t1 a t.
(t1 -> IO (FunPtr a)) -> (t -> t1) -> t -> Opt -> IO (FunPtr a)
exportFunPtr CFunc a -> IO (FunPtr (CFunc a))
forall a. CFunc a -> IO (FunPtr (CFunc a))
mkCFunction ScalarFunction a -> CFunc a
forall a. ScalarFunction a -> CFunc a
wrapCFunction ScalarFunction a
objfun Opt
opt
precfunptr <-
exportFunPtr mkPreconditionerFunction wrapPreconditioner precfun opt
userptr <- getStablePtr opt userdata
withOpt opt $ \NloptOpt
o ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
NloptOpt
-> FunPtr (CFunc a)
-> FunPtr (CPrecond a)
-> StablePtr a
-> CDouble
-> IO CInt
forall a.
NloptOpt
-> FunPtr (CFunc a)
-> FunPtr (CPrecond a)
-> StablePtr a
-> CDouble
-> IO CInt
nlopt_add_precond_equality_constraint NloptOpt
o FunPtr (CFunc a)
objfunptr
FunPtr (CPrecond a)
precfunptr StablePtr a
userptr (Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
tol)
add_equality_mconstraint :: Opt -> Word -> VectorFunction a -> a
-> Double -> IO Result
add_equality_mconstraint :: forall a.
Opt -> Word -> VectorFunction a -> a -> Double -> IO Result
add_equality_mconstraint Opt
opt Word
constraintsize VectorFunction a
constrfun a
userdata Double
tol = do
constrfunptr <- (CMFunc a -> IO (FunPtr (CMFunc a)))
-> (VectorFunction a -> CMFunc a)
-> VectorFunction a
-> Opt
-> IO (FunPtr (CMFunc a))
forall t1 a t.
(t1 -> IO (FunPtr a)) -> (t -> t1) -> t -> Opt -> IO (FunPtr a)
exportFunPtr CMFunc a -> IO (FunPtr (CMFunc a))
forall a. CMFunc a -> IO (FunPtr (CMFunc a))
mkMFunction VectorFunction a -> CMFunc a
forall a. VectorFunction a -> CMFunc a
wrapMFunction VectorFunction a
constrfun Opt
opt
userptr <- getStablePtr opt userdata
withOpt opt $ \NloptOpt
o ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
NloptOpt
-> CUInt -> FunPtr (CMFunc a) -> StablePtr a -> CDouble -> IO CInt
forall a.
NloptOpt
-> CUInt -> FunPtr (CMFunc a) -> StablePtr a -> CDouble -> IO CInt
nlopt_add_equality_mconstraint NloptOpt
o (Word -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
constraintsize)
FunPtr (CMFunc a)
constrfunptr StablePtr a
userptr (Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
tol)
withInputVector :: (Storable c, Storable a)
=> V.Vector c -> (Ptr a -> IO b) -> IO b
withInputVector :: forall c a b.
(Storable c, Storable a) =>
Vector c -> (Ptr a -> IO b) -> IO b
withInputVector = ForeignPtr a -> (Ptr a -> IO b) -> IO b
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (ForeignPtr a -> (Ptr a -> IO b) -> IO b)
-> (Vector c -> ForeignPtr a)
-> Vector c
-> (Ptr a -> IO b)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ForeignPtr a, Int) -> ForeignPtr a
forall a b. (a, b) -> a
fst ((ForeignPtr a, Int) -> ForeignPtr a)
-> (Vector c -> (ForeignPtr a, Int)) -> Vector c -> ForeignPtr a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector a -> (ForeignPtr a, Int)
forall a. Vector a -> (ForeignPtr a, Int)
V.unsafeToForeignPtr0 (Vector a -> (ForeignPtr a, Int))
-> (Vector c -> Vector a) -> Vector c -> (ForeignPtr a, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector c -> Vector a
forall a b. (Storable a, Storable b) => Vector a -> Vector b
V.unsafeCast
withOutputVector :: (Storable c, Storable a)
=> V.MVector s c -> (Ptr a -> IO b) -> IO b
withOutputVector :: forall c a s b.
(Storable c, Storable a) =>
MVector s c -> (Ptr a -> IO b) -> IO b
withOutputVector = ForeignPtr a -> (Ptr a -> IO b) -> IO b
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (ForeignPtr a -> (Ptr a -> IO b) -> IO b)
-> (MVector s c -> ForeignPtr a)
-> MVector s c
-> (Ptr a -> IO b)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ForeignPtr a, Int) -> ForeignPtr a
forall a b. (a, b) -> a
fst ((ForeignPtr a, Int) -> ForeignPtr a)
-> (MVector s c -> (ForeignPtr a, Int))
-> MVector s c
-> ForeignPtr a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MVector s a -> (ForeignPtr a, Int)
forall s a. MVector s a -> (ForeignPtr a, Int)
MV.unsafeToForeignPtr0 (MVector s a -> (ForeignPtr a, Int))
-> (MVector s c -> MVector s a)
-> MVector s c
-> (ForeignPtr a, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MVector s c -> MVector s a
forall a b s.
(Storable a, Storable b) =>
MVector s a -> MVector s b
MV.unsafeCast
setScalar :: (Enum a, Integral b) => (NloptOpt -> t1 -> IO b)
-> (t -> t1) -> Opt -> t -> IO a
setScalar :: forall a b t1 t.
(Enum a, Integral b) =>
(NloptOpt -> t1 -> IO b) -> (t -> t1) -> Opt -> t -> IO a
setScalar NloptOpt -> t1 -> IO b
setter t -> t1
conv Opt
opt t
val = Opt -> (NloptOpt -> IO a) -> IO a
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
opt ((NloptOpt -> IO a) -> IO a) -> (NloptOpt -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \NloptOpt
o ->
b -> a
forall a b. (Integral a, Enum b) => a -> b
parseEnum (b -> a) -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> t1 -> IO b
setter NloptOpt
o (t -> t1
conv t
val)
getScalar :: (NloptOpt -> IO b) -> (b -> a) -> Opt -> IO a
getScalar :: forall b a. (NloptOpt -> IO b) -> (b -> a) -> Opt -> IO a
getScalar NloptOpt -> IO b
getter b -> a
conv = (NloptOpt -> IO a) -> Opt -> IO a
forall a. (NloptOpt -> IO a) -> Opt -> IO a
useOpt ((NloptOpt -> IO a) -> Opt -> IO a)
-> (NloptOpt -> IO a) -> Opt -> IO a
forall a b. (a -> b) -> a -> b
$ (b -> a) -> IO b -> IO a
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> a
conv (IO b -> IO a) -> (NloptOpt -> IO b) -> NloptOpt -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NloptOpt -> IO b
getter
foreign import ccall "nlopt.h nlopt_set_stopval"
nlopt_set_stopval :: NloptOpt -> CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_get_stopval"
nlopt_get_stopval :: NloptOpt -> IO CDouble
set_stopval :: Opt -> Double -> IO Result
set_stopval :: Opt -> Double -> IO Result
set_stopval = (NloptOpt -> CDouble -> IO CInt)
-> (Double -> CDouble) -> Opt -> Double -> IO Result
forall a b t1 t.
(Enum a, Integral b) =>
(NloptOpt -> t1 -> IO b) -> (t -> t1) -> Opt -> t -> IO a
setScalar NloptOpt -> CDouble -> IO CInt
nlopt_set_stopval Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac
get_stopval :: Opt -> IO Double
get_stopval :: Opt -> IO Double
get_stopval = (NloptOpt -> IO CDouble) -> (CDouble -> Double) -> Opt -> IO Double
forall b a. (NloptOpt -> IO b) -> (b -> a) -> Opt -> IO a
getScalar NloptOpt -> IO CDouble
nlopt_get_stopval CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac
foreign import ccall "nlopt.h nlopt_set_ftol_rel"
nlopt_set_ftol_rel :: NloptOpt -> CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_get_ftol_rel"
nlopt_get_ftol_rel :: NloptOpt -> IO CDouble
set_ftol_rel :: Opt -> Double -> IO Result
set_ftol_rel :: Opt -> Double -> IO Result
set_ftol_rel = (NloptOpt -> CDouble -> IO CInt)
-> (Double -> CDouble) -> Opt -> Double -> IO Result
forall a b t1 t.
(Enum a, Integral b) =>
(NloptOpt -> t1 -> IO b) -> (t -> t1) -> Opt -> t -> IO a
setScalar NloptOpt -> CDouble -> IO CInt
nlopt_set_ftol_rel Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac
get_ftol_rel :: Opt -> IO Double
get_ftol_rel :: Opt -> IO Double
get_ftol_rel = (NloptOpt -> IO CDouble) -> (CDouble -> Double) -> Opt -> IO Double
forall b a. (NloptOpt -> IO b) -> (b -> a) -> Opt -> IO a
getScalar NloptOpt -> IO CDouble
nlopt_get_ftol_rel CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac
foreign import ccall "nlopt.h nlopt_set_ftol_abs"
nlopt_set_ftol_abs :: NloptOpt -> CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_get_ftol_abs"
nlopt_get_ftol_abs :: NloptOpt -> IO CDouble
set_ftol_abs :: Opt -> Double -> IO Result
set_ftol_abs :: Opt -> Double -> IO Result
set_ftol_abs = (NloptOpt -> CDouble -> IO CInt)
-> (Double -> CDouble) -> Opt -> Double -> IO Result
forall a b t1 t.
(Enum a, Integral b) =>
(NloptOpt -> t1 -> IO b) -> (t -> t1) -> Opt -> t -> IO a
setScalar NloptOpt -> CDouble -> IO CInt
nlopt_set_ftol_abs Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac
get_ftol_abs :: Opt -> IO Double
get_ftol_abs :: Opt -> IO Double
get_ftol_abs = (NloptOpt -> IO CDouble) -> (CDouble -> Double) -> Opt -> IO Double
forall b a. (NloptOpt -> IO b) -> (b -> a) -> Opt -> IO a
getScalar NloptOpt -> IO CDouble
nlopt_get_ftol_abs CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac
foreign import ccall "nlopt.h nlopt_set_xtol_rel"
nlopt_set_xtol_rel :: NloptOpt -> CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_get_xtol_rel"
nlopt_get_xtol_rel :: NloptOpt -> IO CDouble
set_xtol_rel :: Opt -> Double -> IO Result
set_xtol_rel :: Opt -> Double -> IO Result
set_xtol_rel = (NloptOpt -> CDouble -> IO CInt)
-> (Double -> CDouble) -> Opt -> Double -> IO Result
forall a b t1 t.
(Enum a, Integral b) =>
(NloptOpt -> t1 -> IO b) -> (t -> t1) -> Opt -> t -> IO a
setScalar NloptOpt -> CDouble -> IO CInt
nlopt_set_xtol_rel Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac
get_xtol_rel :: Opt -> IO Double
get_xtol_rel :: Opt -> IO Double
get_xtol_rel = (NloptOpt -> IO CDouble) -> (CDouble -> Double) -> Opt -> IO Double
forall b a. (NloptOpt -> IO b) -> (b -> a) -> Opt -> IO a
getScalar NloptOpt -> IO CDouble
nlopt_get_xtol_rel CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac
foreign import ccall "nlopt.h nlopt_set_xtol_abs1"
nlopt_set_xtol_abs1 :: NloptOpt -> CDouble -> IO CInt
set_xtol_abs1 :: Opt -> Double -> IO Result
set_xtol_abs1 :: Opt -> Double -> IO Result
set_xtol_abs1 = (NloptOpt -> CDouble -> IO CInt)
-> (Double -> CDouble) -> Opt -> Double -> IO Result
forall a b t1 t.
(Enum a, Integral b) =>
(NloptOpt -> t1 -> IO b) -> (t -> t1) -> Opt -> t -> IO a
setScalar NloptOpt -> CDouble -> IO CInt
nlopt_set_xtol_abs1 Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac
foreign import ccall "nlopt.h nlopt_set_xtol_abs"
nlopt_set_xtol_abs :: NloptOpt -> Ptr CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_get_xtol_abs"
nlopt_get_xtol_abs :: NloptOpt -> Ptr CDouble -> IO CInt
set_xtol_abs :: Opt -> V.Vector Double -> IO Result
set_xtol_abs :: Opt -> Vector Double -> IO Result
set_xtol_abs Opt
opt Vector Double
tolvec =
Vector Double -> (Ptr CDouble -> IO Result) -> IO Result
forall c a b.
(Storable c, Storable a) =>
Vector c -> (Ptr a -> IO b) -> IO b
withInputVector Vector Double
tolvec ((Ptr CDouble -> IO Result) -> IO Result)
-> (Ptr CDouble -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \Ptr CDouble
tolptr ->
Opt -> (NloptOpt -> IO Result) -> IO Result
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
opt ((NloptOpt -> IO Result) -> IO Result)
-> (NloptOpt -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \NloptOpt
o -> CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> Ptr CDouble -> IO CInt
nlopt_set_xtol_abs NloptOpt
o Ptr CDouble
tolptr
get_xtol_abs :: Opt -> IO (Result, V.Vector Double)
get_xtol_abs :: Opt -> IO (Result, Vector Double)
get_xtol_abs Opt
opt = do
mutv <- Opt -> IO Word
get_dimension Opt
opt IO Word -> (Word -> IO (IOVector Double)) -> IO (IOVector Double)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> IO (IOVector Double)
Int -> IO (MVector (PrimState IO) Double)
forall (m :: * -> *) a.
(PrimMonad m, Storable a) =>
Int -> m (MVector (PrimState m) a)
MV.new (Int -> IO (IOVector Double))
-> (Word -> Int) -> Word -> IO (IOVector Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
withOutputVector mutv $ \Ptr CDouble
vecptr ->
Opt
-> (NloptOpt -> IO (Result, Vector Double))
-> IO (Result, Vector Double)
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
opt ((NloptOpt -> IO (Result, Vector Double))
-> IO (Result, Vector Double))
-> (NloptOpt -> IO (Result, Vector Double))
-> IO (Result, Vector Double)
forall a b. (a -> b) -> a -> b
$ \NloptOpt
o -> do
result <- CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> Ptr CDouble -> IO CInt
nlopt_get_xtol_abs NloptOpt
o Ptr CDouble
vecptr
outvec <- V.unsafeFreeze mutv
return (result, outvec)
foreign import ccall "nlopt.h nlopt_set_maxeval"
nlopt_set_maxeval :: NloptOpt -> CInt -> IO CInt
foreign import ccall "nlopt.h nlopt_get_maxeval"
nlopt_get_maxeval :: NloptOpt -> IO CInt
set_maxeval :: Opt -> Word -> IO Result
set_maxeval :: Opt -> Word -> IO Result
set_maxeval = (NloptOpt -> CInt -> IO CInt)
-> (Word -> CInt) -> Opt -> Word -> IO Result
forall a b t1 t.
(Enum a, Integral b) =>
(NloptOpt -> t1 -> IO b) -> (t -> t1) -> Opt -> t -> IO a
setScalar NloptOpt -> CInt -> IO CInt
nlopt_set_maxeval Word -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral
get_maxeval :: Opt -> IO Word
get_maxeval :: Opt -> IO Word
get_maxeval = (NloptOpt -> IO CInt) -> (CInt -> Word) -> Opt -> IO Word
forall b a. (NloptOpt -> IO b) -> (b -> a) -> Opt -> IO a
getScalar NloptOpt -> IO CInt
nlopt_get_maxeval CInt -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
foreign import ccall "nlopt.h nlopt_set_maxtime"
nlopt_set_maxtime :: NloptOpt -> CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_get_maxtime"
nlopt_get_maxtime :: NloptOpt -> IO CDouble
set_maxtime :: Opt -> Double -> IO Result
set_maxtime :: Opt -> Double -> IO Result
set_maxtime = (NloptOpt -> CDouble -> IO CInt)
-> (Double -> CDouble) -> Opt -> Double -> IO Result
forall a b t1 t.
(Enum a, Integral b) =>
(NloptOpt -> t1 -> IO b) -> (t -> t1) -> Opt -> t -> IO a
setScalar NloptOpt -> CDouble -> IO CInt
nlopt_set_maxtime Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac
get_maxtime :: Opt -> IO Double
get_maxtime :: Opt -> IO Double
get_maxtime = (NloptOpt -> IO CDouble) -> (CDouble -> Double) -> Opt -> IO Double
forall b a. (NloptOpt -> IO b) -> (b -> a) -> Opt -> IO a
getScalar NloptOpt -> IO CDouble
nlopt_get_maxtime CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac
foreign import ccall "nlopt.h nlopt_force_stop"
nlopt_force_stop :: NloptOpt -> IO CInt
force_stop :: Opt -> IO Result
force_stop :: Opt -> IO Result
force_stop = (NloptOpt -> IO Result) -> Opt -> IO Result
forall a. (NloptOpt -> IO a) -> Opt -> IO a
useOpt ((NloptOpt -> IO Result) -> Opt -> IO Result)
-> (NloptOpt -> IO Result) -> Opt -> IO Result
forall a b. (a -> b) -> a -> b
$ (CInt -> Result) -> IO CInt -> IO Result
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (IO CInt -> IO Result)
-> (NloptOpt -> IO CInt) -> NloptOpt -> IO Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NloptOpt -> IO CInt
nlopt_force_stop
foreign import ccall "nlopt.h nlopt_set_force_stop"
nlopt_set_force_stop :: NloptOpt -> CInt -> IO CInt
foreign import ccall "nlopt.h nlopt_get_force_stop"
nlopt_get_force_stop :: NloptOpt -> IO CInt
set_force_stop :: Opt -> Word -> IO Result
set_force_stop :: Opt -> Word -> IO Result
set_force_stop = (NloptOpt -> CInt -> IO CInt)
-> (Word -> CInt) -> Opt -> Word -> IO Result
forall a b t1 t.
(Enum a, Integral b) =>
(NloptOpt -> t1 -> IO b) -> (t -> t1) -> Opt -> t -> IO a
setScalar NloptOpt -> CInt -> IO CInt
nlopt_set_force_stop Word -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral
get_force_stop :: Opt -> IO Word
get_force_stop :: Opt -> IO Word
get_force_stop = (NloptOpt -> IO CInt) -> (CInt -> Word) -> Opt -> IO Word
forall b a. (NloptOpt -> IO b) -> (b -> a) -> Opt -> IO a
getScalar NloptOpt -> IO CInt
nlopt_get_force_stop CInt -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
foreign import ccall "nlopt.h nlopt_set_local_optimizer"
nlopt_set_local_optimizer :: NloptOpt -> NloptOpt -> IO CInt
set_local_optimizer :: Opt
-> Opt
-> IO Result
set_local_optimizer :: Opt -> Opt -> IO Result
set_local_optimizer Opt
p Opt
s =
Opt -> (NloptOpt -> IO Result) -> IO Result
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
p ((NloptOpt -> IO Result) -> IO Result)
-> (NloptOpt -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \NloptOpt
primary -> Opt -> (NloptOpt -> IO Result) -> IO Result
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
s ((NloptOpt -> IO Result) -> IO Result)
-> (NloptOpt -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \NloptOpt
secondary ->
CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> NloptOpt -> IO CInt
nlopt_set_local_optimizer NloptOpt
primary NloptOpt
secondary
foreign import ccall "nlopt.h nlopt_set_population"
nlopt_set_population :: NloptOpt -> Word -> IO CInt
foreign import ccall "nlopt.h nlopt_get_population"
nlopt_get_population :: NloptOpt -> IO Word
set_population :: Opt -> Word -> IO Result
set_population :: Opt -> Word -> IO Result
set_population = (NloptOpt -> Word -> IO CInt)
-> (Word -> Word) -> Opt -> Word -> IO Result
forall a b t1 t.
(Enum a, Integral b) =>
(NloptOpt -> t1 -> IO b) -> (t -> t1) -> Opt -> t -> IO a
setScalar NloptOpt -> Word -> IO CInt
nlopt_set_population Word -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
get_population :: Opt -> IO Word
get_population :: Opt -> IO Word
get_population = (NloptOpt -> IO Word) -> (Word -> Word) -> Opt -> IO Word
forall b a. (NloptOpt -> IO b) -> (b -> a) -> Opt -> IO a
getScalar NloptOpt -> IO Word
nlopt_get_population Word -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
foreign import ccall "nlopt.h nlopt_set_vector_storage"
nlopt_set_vector_storage :: NloptOpt -> Word -> IO CInt
foreign import ccall "nlopt.h nlopt_get_vector_storage"
nlopt_get_vector_storage :: NloptOpt -> IO Word
set_vector_storage :: Opt -> Word -> IO Result
set_vector_storage :: Opt -> Word -> IO Result
set_vector_storage = (NloptOpt -> Word -> IO CInt)
-> (Word -> Word) -> Opt -> Word -> IO Result
forall a b t1 t.
(Enum a, Integral b) =>
(NloptOpt -> t1 -> IO b) -> (t -> t1) -> Opt -> t -> IO a
setScalar NloptOpt -> Word -> IO CInt
nlopt_set_vector_storage Word -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
get_vector_storage :: Opt -> IO Word
get_vector_storage :: Opt -> IO Word
get_vector_storage = (NloptOpt -> IO Word) -> (Word -> Word) -> Opt -> IO Word
forall b a. (NloptOpt -> IO b) -> (b -> a) -> Opt -> IO a
getScalar NloptOpt -> IO Word
nlopt_get_vector_storage Word -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
foreign import ccall "nlopt.h nlopt_set_default_initial_step"
nlopt_set_default_initial_step :: NloptOpt -> Ptr CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_set_initial_step"
nlopt_set_initial_step :: NloptOpt -> Ptr CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_set_initial_step1"
nlopt_set_initial_step1 :: NloptOpt -> CDouble -> IO CInt
foreign import ccall "nlopt.h nlopt_get_initial_step"
nlopt_get_initial_step :: NloptOpt -> Ptr CDouble -> Ptr CDouble -> IO CInt
set_default_initial_step :: Opt -> V.Vector Double -> IO Result
set_default_initial_step :: Opt -> Vector Double -> IO Result
set_default_initial_step Opt
opt Vector Double
stepvec =
Vector Double -> (Ptr CDouble -> IO Result) -> IO Result
forall c a b.
(Storable c, Storable a) =>
Vector c -> (Ptr a -> IO b) -> IO b
withInputVector Vector Double
stepvec ((Ptr CDouble -> IO Result) -> IO Result)
-> (Ptr CDouble -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \Ptr CDouble
stepptr ->
Opt -> (NloptOpt -> IO Result) -> IO Result
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
opt ((NloptOpt -> IO Result) -> IO Result)
-> (NloptOpt -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \NloptOpt
o -> CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> Ptr CDouble -> IO CInt
nlopt_set_default_initial_step NloptOpt
o Ptr CDouble
stepptr
set_initial_step :: Opt -> V.Vector Double -> IO Result
set_initial_step :: Opt -> Vector Double -> IO Result
set_initial_step Opt
opt Vector Double
stepvec =
Vector Double -> (Ptr CDouble -> IO Result) -> IO Result
forall c a b.
(Storable c, Storable a) =>
Vector c -> (Ptr a -> IO b) -> IO b
withInputVector Vector Double
stepvec ((Ptr CDouble -> IO Result) -> IO Result)
-> (Ptr CDouble -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \Ptr CDouble
stepptr ->
Opt -> (NloptOpt -> IO Result) -> IO Result
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
opt ((NloptOpt -> IO Result) -> IO Result)
-> (NloptOpt -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \NloptOpt
o -> CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> Ptr CDouble -> IO CInt
nlopt_set_initial_step NloptOpt
o Ptr CDouble
stepptr
set_initial_step1 :: Opt -> Double -> IO Result
set_initial_step1 :: Opt -> Double -> IO Result
set_initial_step1 = (NloptOpt -> CDouble -> IO CInt)
-> (Double -> CDouble) -> Opt -> Double -> IO Result
forall a b t1 t.
(Enum a, Integral b) =>
(NloptOpt -> t1 -> IO b) -> (t -> t1) -> Opt -> t -> IO a
setScalar NloptOpt -> CDouble -> IO CInt
nlopt_set_initial_step1 Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac
get_initial_step :: Opt -> V.Vector Double -> IO (Result, V.Vector Double)
get_initial_step :: Opt -> Vector Double -> IO (Result, Vector Double)
get_initial_step Opt
opt Vector Double
xvec = do
mutv <- Opt -> IO Word
get_dimension Opt
opt IO Word -> (Word -> IO (IOVector Double)) -> IO (IOVector Double)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> IO (IOVector Double)
Int -> IO (MVector (PrimState IO) Double)
forall (m :: * -> *) a.
(PrimMonad m, Storable a) =>
Int -> m (MVector (PrimState m) a)
MV.new (Int -> IO (IOVector Double))
-> (Word -> Int) -> Word -> IO (IOVector Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
withOutputVector mutv $ \Ptr CDouble
outptr ->
Vector Double
-> (Ptr CDouble -> IO (Result, Vector Double))
-> IO (Result, Vector Double)
forall c a b.
(Storable c, Storable a) =>
Vector c -> (Ptr a -> IO b) -> IO b
withInputVector Vector Double
xvec ((Ptr CDouble -> IO (Result, Vector Double))
-> IO (Result, Vector Double))
-> (Ptr CDouble -> IO (Result, Vector Double))
-> IO (Result, Vector Double)
forall a b. (a -> b) -> a -> b
$ \Ptr CDouble
inptr ->
Opt
-> (NloptOpt -> IO (Result, Vector Double))
-> IO (Result, Vector Double)
forall a. Opt -> (NloptOpt -> IO a) -> IO a
withOpt Opt
opt ((NloptOpt -> IO (Result, Vector Double))
-> IO (Result, Vector Double))
-> (NloptOpt -> IO (Result, Vector Double))
-> IO (Result, Vector Double)
forall a b. (a -> b) -> a -> b
$ \NloptOpt
o -> do
result <- CInt -> Result
forall a b. (Integral a, Enum b) => a -> b
parseEnum (CInt -> Result) -> IO CInt -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NloptOpt -> Ptr CDouble -> Ptr CDouble -> IO CInt
nlopt_get_initial_step NloptOpt
o Ptr CDouble
inptr Ptr CDouble
outptr
outvec <- V.unsafeFreeze mutv
return (result, outvec)