aboutsummaryrefslogtreecommitdiff
path: root/Math
diff options
context:
space:
mode:
Diffstat (limited to 'Math')
-rw-r--r--Math/LinProg/Compile.hs3
-rw-r--r--Math/LinProg/LP.hs2
-rw-r--r--Math/LinProg/LPSolve/FFI.hs22
-rw-r--r--Math/LinProg/Types.hs1
4 files changed, 16 insertions, 12 deletions
diff --git a/Math/LinProg/Compile.hs b/Math/LinProg/Compile.hs
index 07398e7..c14d45b 100644
--- a/Math/LinProg/Compile.hs
+++ b/Math/LinProg/Compile.hs
@@ -9,12 +9,9 @@ module Math.LinProg.Compile (
,leqs
) where
-import Data.List
import Math.LinProg.Types
import Control.Lens
-import Control.Monad.State
import Control.Monad.Free
-import Data.Maybe
type Equation t v = (LinExpr t v, t) -- LHS and RHS
diff --git a/Math/LinProg/LP.hs b/Math/LinProg/LP.hs
index 4ad8b79..50bcb1f 100644
--- a/Math/LinProg/LP.hs
+++ b/Math/LinProg/LP.hs
@@ -8,8 +8,6 @@ import Data.List
import Math.LinProg.Types
import Math.LinProg.Compile
import Control.Lens
-import Control.Monad.State
-import Control.Monad.Free
import Data.Maybe
instance (Show t, Num t, Ord t) => Show (CompilerS t String) where
diff --git a/Math/LinProg/LPSolve/FFI.hs b/Math/LinProg/LPSolve/FFI.hs
index eb818df..45b0a30 100644
--- a/Math/LinProg/LPSolve/FFI.hs
+++ b/Math/LinProg/LPSolve/FFI.hs
@@ -1,9 +1,19 @@
{-# LANGUAGE ForeignFunctionInterface #-}
-module Math.LinProg.LPSolve.FFI where
+module Math.LinProg.LPSolve.FFI (
+ ResultCode(..)
+ ,ConstraintType(..)
+ ,LPRec
+ ,setConstrType
+ ,makeLP
+ ,freeLP
+ ,setMat
+ ,setRHS
+ ,solve
+ ,getSol
+) where
import Foreign
import Foreign.C
-import Foreign.Marshal.Array
import Control.Applicative ((<$>))
import qualified Data.Map as M
@@ -46,11 +56,11 @@ setConstrType lp i t = fromIntegral <$> c_set_constr_type lp (fromIntegral i) (f
makeLP :: Int -> Int -> IO (Maybe LPRec)
makeLP n m = do
- m <- c_make_lp (fromIntegral n) (fromIntegral m)
- return $ if m == nullPtr then
+ m' <- c_make_lp (fromIntegral n) (fromIntegral m)
+ return $ if m' == nullPtr then
Nothing
else
- Just m
+ Just m'
freeLP :: LPRec -> IO ()
freeLP m = with m $ \m' -> c_free_lp m'
@@ -66,7 +76,7 @@ solve lp = (lut M.!) . fromIntegral <$> c_solve lp
where
lut = M.fromList [
(-2, NoMemory)
- ,(0, Optimal)
+ ,(0 :: Int, Optimal)
,(1, SubOptimal)
,(2, Infeasible)
,(3, Unbounded)
diff --git a/Math/LinProg/Types.hs b/Math/LinProg/Types.hs
index 8b95ef0..69da6bf 100644
--- a/Math/LinProg/Types.hs
+++ b/Math/LinProg/Types.hs
@@ -20,7 +20,6 @@ module Math.LinProg.Types (
import Data.Functor.Foldable
import Control.Monad.Free
-import qualified Data.Map as M
data LinExpr' t v a =
Lit t