aboutsummaryrefslogtreecommitdiff
path: root/Math
diff options
context:
space:
mode:
Diffstat (limited to 'Math')
-rw-r--r--Math/LinProg/Compile.hs37
-rw-r--r--Math/LinProg/LP.hs32
-rw-r--r--Math/LinProg/LPSolve.hs2
3 files changed, 31 insertions, 40 deletions
diff --git a/Math/LinProg/Compile.hs b/Math/LinProg/Compile.hs
deleted file mode 100644
index c14d45b..0000000
--- a/Math/LinProg/Compile.hs
+++ /dev/null
@@ -1,37 +0,0 @@
-{-# LANGUAGE TemplateHaskell, FlexibleInstances, ScopedTypeVariables #-}
-
-module Math.LinProg.Compile (
- compile
- ,Equation
- ,CompilerS(..)
- ,objective
- ,equals
- ,leqs
-) where
-
-import Math.LinProg.Types
-import Control.Lens
-import Control.Monad.Free
-
-type Equation t v = (LinExpr t v, t) -- LHS and RHS
-
-data CompilerS t v = CompilerS {
- _objective :: LinExpr t v
- ,_equals :: [Equation t v]
- ,_leqs :: [Equation t v]
-} deriving (Eq)
-
-$(makeLenses ''CompilerS)
-
-compile :: (Num t, Show t, Ord t, Eq v) => LinProg t v () -> CompilerS t v
-compile ast = compile' ast initCompilerS where
- compile' (Free (Objective a c)) state = compile' c $ state & objective +~ a
- compile' (Free (EqConstraint a b c)) state = compile' c $ state & equals %~ (split (a-b):)
- compile' (Free (LeqConstraint a b c)) state = compile' c $ state & leqs %~ (split (a-b):)
- compile' _ state = state
-
- initCompilerS = CompilerS
- 0
- []
- []
-
diff --git a/Math/LinProg/LP.hs b/Math/LinProg/LP.hs
index 50bcb1f..5f9e168 100644
--- a/Math/LinProg/LP.hs
+++ b/Math/LinProg/LP.hs
@@ -1,15 +1,43 @@
-{-# LANGUAGE FlexibleInstances, ScopedTypeVariables #-}
+{-# LANGUAGE TemplateHaskell, FlexibleInstances, ScopedTypeVariables #-}
module Math.LinProg.LP (
compile
+ ,Equation
+ ,CompilerS(..)
+ ,objective
+ ,equals
+ ,leqs
) where
import Data.List
import Math.LinProg.Types
-import Math.LinProg.Compile
import Control.Lens
import Data.Maybe
+import Control.Monad.Free
+type Equation t v = (LinExpr t v, t) -- LHS and RHS
+
+data CompilerS t v = CompilerS {
+ _objective :: LinExpr t v
+ ,_equals :: [Equation t v]
+ ,_leqs :: [Equation t v]
+} deriving (Eq)
+
+$(makeLenses ''CompilerS)
+
+compile :: (Num t, Show t, Ord t, Eq v) => LinProg t v () -> CompilerS t v
+compile ast = compile' ast initCompilerS where
+ compile' (Free (Objective a c)) state = compile' c $ state & objective +~ a
+ compile' (Free (EqConstraint a b c)) state = compile' c $ state & equals %~ (split (a-b):)
+ compile' (Free (LeqConstraint a b c)) state = compile' c $ state & leqs %~ (split (a-b):)
+ compile' _ state = state
+
+ initCompilerS = CompilerS
+ 0
+ []
+ []
+
+-- Printing to LP format
instance (Show t, Num t, Ord t) => Show (CompilerS t String) where
show s = unlines $ catMaybes [
Just "Minimize"
diff --git a/Math/LinProg/LPSolve.hs b/Math/LinProg/LPSolve.hs
index 85f536d..7b1f8ca 100644
--- a/Math/LinProg/LPSolve.hs
+++ b/Math/LinProg/LPSolve.hs
@@ -11,7 +11,7 @@ import Data.List
import Control.Lens
import Math.LinProg.LPSolve.FFI hiding (solve)
import qualified Math.LinProg.LPSolve.FFI as F
-import Math.LinProg.Compile
+import Math.LinProg.LP
import Math.LinProg.Types
import qualified Data.Map as M
import Prelude hiding (EQ)