Statistics
| Branch: | Tag: | Revision:

root / hbal.hs @ d09b6ed3

History | View | Annotate | Download (11.7 kB)

1 e4f08c46 Iustin Pop
{-| Solver for N+1 cluster errors
2 e4f08c46 Iustin Pop
3 e4f08c46 Iustin Pop
-}
4 e4f08c46 Iustin Pop
5 e4f08c46 Iustin Pop
module Main (main) where
6 e4f08c46 Iustin Pop
7 e4f08c46 Iustin Pop
import Data.List
8 e4f08c46 Iustin Pop
import Data.Function
9 e0eb63f0 Iustin Pop
import Data.Maybe (isJust, fromJust, fromMaybe)
10 e4f08c46 Iustin Pop
import Monad
11 e4f08c46 Iustin Pop
import System
12 e4f08c46 Iustin Pop
import System.IO
13 e4f08c46 Iustin Pop
import System.Console.GetOpt
14 e4f08c46 Iustin Pop
import qualified System
15 e4f08c46 Iustin Pop
16 e4f08c46 Iustin Pop
import Text.Printf (printf)
17 e4f08c46 Iustin Pop
18 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Container as Container
19 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
20 ec18dca9 Iustin Pop
import qualified Ganeti.HTools.Node as Node
21 209b3711 Iustin Pop
import qualified Ganeti.HTools.CLI as CLI
22 669d7e3d Iustin Pop
import Ganeti.HTools.Rapi
23 669d7e3d Iustin Pop
import Ganeti.HTools.Utils
24 e4f08c46 Iustin Pop
25 e4f08c46 Iustin Pop
-- | Command line options structure.
26 e4f08c46 Iustin Pop
data Options = Options
27 e0eb63f0 Iustin Pop
    { optShowNodes :: Bool           -- ^ Whether to show node status
28 e0eb63f0 Iustin Pop
    , optShowCmds  :: Maybe FilePath -- ^ Whether to show the command list
29 e0eb63f0 Iustin Pop
    , optOneline   :: Bool           -- ^ Switch output to a single line
30 e0eb63f0 Iustin Pop
    , optNodef     :: FilePath       -- ^ Path to the nodes file
31 8032b3b5 Iustin Pop
    , optNodeSet   :: Bool           -- ^ The nodes have been set by options
32 e0eb63f0 Iustin Pop
    , optInstf     :: FilePath       -- ^ Path to the instances file
33 8032b3b5 Iustin Pop
    , optInstSet   :: Bool           -- ^ The insts have been set by options
34 e0eb63f0 Iustin Pop
    , optMaxLength :: Int            -- ^ Stop after this many steps
35 e0eb63f0 Iustin Pop
    , optMaster    :: String         -- ^ Collect data from RAPI
36 e0eb63f0 Iustin Pop
    , optVerbose   :: Int            -- ^ Verbosity level
37 e0eb63f0 Iustin Pop
    , optOffline   :: [String]       -- ^ Names of offline nodes
38 b0517d61 Iustin Pop
    , optMinScore  :: Cluster.Score  -- ^ The minimum score we aim for
39 e0eb63f0 Iustin Pop
    , optShowVer   :: Bool           -- ^ Just show the program version
40 e0eb63f0 Iustin Pop
    , optShowHelp  :: Bool           -- ^ Just show the help
41 e4f08c46 Iustin Pop
    } deriving Show
42 e4f08c46 Iustin Pop
43 e4f08c46 Iustin Pop
-- | Default values for the command line options.
44 e4f08c46 Iustin Pop
defaultOptions :: Options
45 e4f08c46 Iustin Pop
defaultOptions  = Options
46 e4f08c46 Iustin Pop
 { optShowNodes = False
47 e0eb63f0 Iustin Pop
 , optShowCmds  = Nothing
48 27f96567 Iustin Pop
 , optOneline   = False
49 e4f08c46 Iustin Pop
 , optNodef     = "nodes"
50 8032b3b5 Iustin Pop
 , optNodeSet   = False
51 e4f08c46 Iustin Pop
 , optInstf     = "instances"
52 8032b3b5 Iustin Pop
 , optInstSet   = False
53 7dfaafb1 Iustin Pop
 , optMaxLength = -1
54 a30b2f5b Iustin Pop
 , optMaster    = ""
55 d09b6ed3 Iustin Pop
 , optVerbose   = 1
56 ec18dca9 Iustin Pop
 , optOffline   = []
57 b0517d61 Iustin Pop
 , optMinScore  = 1e-9
58 209b3711 Iustin Pop
 , optShowVer   = False
59 209b3711 Iustin Pop
 , optShowHelp  = False
60 e4f08c46 Iustin Pop
 }
61 e4f08c46 Iustin Pop
62 e4f08c46 Iustin Pop
-- | Options list and functions
63 e4f08c46 Iustin Pop
options :: [OptDescr (Options -> Options)]
64 e4f08c46 Iustin Pop
options =
65 e4f08c46 Iustin Pop
    [ Option ['p']     ["print-nodes"]
66 e4f08c46 Iustin Pop
      (NoArg (\ opts -> opts { optShowNodes = True }))
67 e4f08c46 Iustin Pop
      "print the final node list"
68 e4f08c46 Iustin Pop
    , Option ['C']     ["print-commands"]
69 e0eb63f0 Iustin Pop
      (OptArg ((\ f opts -> opts { optShowCmds = Just f }) . fromMaybe "-")
70 e0eb63f0 Iustin Pop
                  "FILE")
71 e0eb63f0 Iustin Pop
      "print the ganeti command list for reaching the solution,\
72 e0eb63f0 Iustin Pop
      \if an argument is passed then write the commands to a file named\
73 e0eb63f0 Iustin Pop
      \ as such"
74 27f96567 Iustin Pop
    , Option ['o']     ["oneline"]
75 27f96567 Iustin Pop
      (NoArg (\ opts -> opts { optOneline = True }))
76 27f96567 Iustin Pop
      "print the ganeti command list for reaching the solution"
77 7eff5b09 Iustin Pop
    , Option ['n']     ["nodes"]
78 8032b3b5 Iustin Pop
      (ReqArg (\ f opts -> opts { optNodef = f, optNodeSet = True }) "FILE")
79 e4f08c46 Iustin Pop
      "the node list FILE"
80 7eff5b09 Iustin Pop
    , Option ['i']     ["instances"]
81 8032b3b5 Iustin Pop
      (ReqArg (\ f opts -> opts { optInstf =  f, optInstSet = True }) "FILE")
82 e4f08c46 Iustin Pop
      "the instance list FILE"
83 7eff5b09 Iustin Pop
    , Option ['m']     ["master"]
84 a30b2f5b Iustin Pop
      (ReqArg (\ m opts -> opts { optMaster = m }) "ADDRESS")
85 a30b2f5b Iustin Pop
      "collect data via RAPI at the given ADDRESS"
86 7eff5b09 Iustin Pop
    , Option ['l']     ["max-length"]
87 7dfaafb1 Iustin Pop
      (ReqArg (\ i opts -> opts { optMaxLength =  (read i)::Int }) "N")
88 7dfaafb1 Iustin Pop
      "cap the solution at this many moves (useful for very unbalanced \
89 7dfaafb1 Iustin Pop
      \clusters)"
90 7eff5b09 Iustin Pop
    , Option ['v']     ["verbose"]
91 209b3711 Iustin Pop
      (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) + 1 }))
92 7eff5b09 Iustin Pop
      "increase the verbosity level"
93 d09b6ed3 Iustin Pop
    , Option ['q']     ["quiet"]
94 d09b6ed3 Iustin Pop
      (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) - 1 }))
95 d09b6ed3 Iustin Pop
      "decrease the verbosity level"
96 ec18dca9 Iustin Pop
    , Option ['O']     ["offline"]
97 ec18dca9 Iustin Pop
      (ReqArg (\ n opts -> opts { optOffline = n:optOffline opts }) "NODE")
98 b0517d61 Iustin Pop
      " set node as offline"
99 b0517d61 Iustin Pop
    , Option ['e']     ["min-score"]
100 b0517d61 Iustin Pop
      (ReqArg (\ e opts -> opts { optMinScore = read e }) "EPSILON")
101 b0517d61 Iustin Pop
      " mininum score to aim for"
102 209b3711 Iustin Pop
    , Option ['V']     ["version"]
103 209b3711 Iustin Pop
      (NoArg (\ opts -> opts { optShowVer = True}))
104 209b3711 Iustin Pop
      "show the version of the program"
105 209b3711 Iustin Pop
    , Option ['h']     ["help"]
106 209b3711 Iustin Pop
      (NoArg (\ opts -> opts { optShowHelp = True}))
107 209b3711 Iustin Pop
      "show help"
108 7ef4d93e Iustin Pop
    ]
109 e4f08c46 Iustin Pop
110 6dc960bc Iustin Pop
{- | Start computing the solution at the given depth and recurse until
111 6dc960bc Iustin Pop
we find a valid solution or we exceed the maximum depth.
112 6dc960bc Iustin Pop
113 6dc960bc Iustin Pop
-}
114 6dc960bc Iustin Pop
iterateDepth :: Cluster.Table    -- ^ The starting table
115 6dc960bc Iustin Pop
             -> Int              -- ^ Remaining length
116 740ec004 Iustin Pop
             -> Cluster.NameList -- ^ Node idx to name list
117 740ec004 Iustin Pop
             -> Cluster.NameList -- ^ Inst idx to name list
118 6dc960bc Iustin Pop
             -> Int              -- ^ Max node name len
119 6dc960bc Iustin Pop
             -> Int              -- ^ Max instance name len
120 6dc960bc Iustin Pop
             -> [[String]]       -- ^ Current command list
121 6dc960bc Iustin Pop
             -> Bool             -- ^ Wheter to be silent
122 b0517d61 Iustin Pop
             -> Cluster.Score    -- ^ Score at which to stop
123 6dc960bc Iustin Pop
             -> IO (Cluster.Table, [[String]]) -- ^ The resulting table and
124 6dc960bc Iustin Pop
                                               -- commands
125 b0517d61 Iustin Pop
iterateDepth ini_tbl max_rounds ktn kti nmlen imlen
126 b0517d61 Iustin Pop
             cmd_strs oneline min_score =
127 6dc960bc Iustin Pop
    let Cluster.Table ini_nl ini_il ini_cv ini_plc = ini_tbl
128 6dc960bc Iustin Pop
        all_inst = Container.elems ini_il
129 ec18dca9 Iustin Pop
        node_idx = map Node.idx . filter (not . Node.offline) $
130 ec18dca9 Iustin Pop
                   Container.elems ini_nl
131 6dc960bc Iustin Pop
        fin_tbl = Cluster.checkMove node_idx ini_tbl all_inst
132 6dc960bc Iustin Pop
        (Cluster.Table _ _ fin_cv fin_plc) = fin_tbl
133 6dc960bc Iustin Pop
        ini_plc_len = length ini_plc
134 6dc960bc Iustin Pop
        fin_plc_len = length fin_plc
135 6dc960bc Iustin Pop
        allowed_next = (max_rounds < 0 || length fin_plc < max_rounds)
136 6dc960bc Iustin Pop
    in
137 6dc960bc Iustin Pop
      do
138 6dc960bc Iustin Pop
        let
139 6dc960bc Iustin Pop
            (sol_line, cmds) = Cluster.printSolutionLine ini_il ktn kti
140 6dc960bc Iustin Pop
                               nmlen imlen (head fin_plc) fin_plc_len
141 6dc960bc Iustin Pop
            upd_cmd_strs = cmds:cmd_strs
142 6dc960bc Iustin Pop
        unless (oneline || fin_plc_len == ini_plc_len) $ do
143 6dc960bc Iustin Pop
          putStrLn sol_line
144 6dc960bc Iustin Pop
          hFlush stdout
145 6dc960bc Iustin Pop
        (if fin_cv < ini_cv then -- this round made success, try deeper
146 b0517d61 Iustin Pop
             if allowed_next && fin_cv > min_score
147 6dc960bc Iustin Pop
             then iterateDepth fin_tbl max_rounds ktn kti
148 b0517d61 Iustin Pop
                  nmlen imlen upd_cmd_strs oneline min_score
149 6dc960bc Iustin Pop
             -- don't go deeper, but return the better solution
150 6dc960bc Iustin Pop
             else return (fin_tbl, upd_cmd_strs)
151 6dc960bc Iustin Pop
         else
152 6dc960bc Iustin Pop
             return (ini_tbl, cmd_strs))
153 6dc960bc Iustin Pop
154 ba6c6006 Iustin Pop
-- | Formats the solution for the oneline display
155 ba6c6006 Iustin Pop
formatOneline :: Double -> Int -> Double -> String
156 ba6c6006 Iustin Pop
formatOneline ini_cv plc_len fin_cv =
157 ba6c6006 Iustin Pop
    printf "%.8f %d %.8f %8.3f" ini_cv plc_len fin_cv
158 ba6c6006 Iustin Pop
               (if fin_cv == 0 then 1 else (ini_cv / fin_cv))
159 ba6c6006 Iustin Pop
160 e4f08c46 Iustin Pop
-- | Main function.
161 e4f08c46 Iustin Pop
main :: IO ()
162 e4f08c46 Iustin Pop
main = do
163 e4f08c46 Iustin Pop
  cmd_args <- System.getArgs
164 45f01962 Iustin Pop
  (opts, args) <- CLI.parseOpts cmd_args "hbal" options
165 45f01962 Iustin Pop
                  defaultOptions optShowHelp
166 45f01962 Iustin Pop
167 45f01962 Iustin Pop
  unless (null args) $ do
168 45f01962 Iustin Pop
         hPutStrLn stderr "Error: this program doesn't take any arguments."
169 45f01962 Iustin Pop
         exitWith $ ExitFailure 1
170 a30b2f5b Iustin Pop
171 7ef4d93e Iustin Pop
  when (optShowVer opts) $ do
172 209b3711 Iustin Pop
         putStr $ CLI.showVersion "hbal"
173 7ef4d93e Iustin Pop
         exitWith ExitSuccess
174 7ef4d93e Iustin Pop
175 8032b3b5 Iustin Pop
  (env_node, env_inst) <- CLI.parseEnv ()
176 8032b3b5 Iustin Pop
  let nodef = if optNodeSet opts then optNodef opts
177 8032b3b5 Iustin Pop
              else env_node
178 8032b3b5 Iustin Pop
      instf = if optInstSet opts then optInstf opts
179 8032b3b5 Iustin Pop
              else env_inst
180 8032b3b5 Iustin Pop
      oneline = optOneline opts
181 7eff5b09 Iustin Pop
      verbose = optVerbose opts
182 7eff5b09 Iustin Pop
      (node_data, inst_data) =
183 a30b2f5b Iustin Pop
          case optMaster opts of
184 8032b3b5 Iustin Pop
            "" -> (readFile nodef,
185 8032b3b5 Iustin Pop
                   readFile instf)
186 a30b2f5b Iustin Pop
            host -> (readData getNodes host,
187 a30b2f5b Iustin Pop
                     readData getInstances host)
188 a30b2f5b Iustin Pop
189 ec18dca9 Iustin Pop
  (loaded_nl, il, csf, ktn, kti) <- liftM2 Cluster.loadData node_data inst_data
190 a1c6212e Iustin Pop
  let (fix_msgs, fixed_nl) = Cluster.checkData loaded_nl il ktn kti
191 a1c6212e Iustin Pop
192 d09b6ed3 Iustin Pop
  unless (null fix_msgs || verbose == 0) $ do
193 a1c6212e Iustin Pop
         putStrLn "Warning: cluster has inconsistent data:"
194 a1c6212e Iustin Pop
         putStrLn . unlines . map (\s -> printf "  - %s" s) $ fix_msgs
195 ec18dca9 Iustin Pop
196 ec18dca9 Iustin Pop
  let offline_names = optOffline opts
197 3d7cd10b Iustin Pop
      all_names = snd . unzip $ ktn
198 3d7cd10b Iustin Pop
      offline_wrong = filter (\n -> not $ elem n all_names) offline_names
199 ec18dca9 Iustin Pop
      offline_indices = fst . unzip .
200 ec18dca9 Iustin Pop
                        filter (\(_, n) -> elem n offline_names) $ ktn
201 ec18dca9 Iustin Pop
202 3d7cd10b Iustin Pop
  when (length offline_wrong > 0) $ do
203 3d7cd10b Iustin Pop
         printf "Wrong node name(s) set as offline: %s\n"
204 3d7cd10b Iustin Pop
                (commaJoin offline_wrong)
205 3d7cd10b Iustin Pop
         exitWith $ ExitFailure 1
206 3d7cd10b Iustin Pop
207 ec18dca9 Iustin Pop
  let nl = Container.map (\n -> if elem (Node.idx n) offline_indices
208 ec18dca9 Iustin Pop
                                then Node.setOffline n True
209 a1c6212e Iustin Pop
                                else n) fixed_nl
210 a30b2f5b Iustin Pop
211 dcbcdb58 Iustin Pop
  when (Container.size il == 0) $ do
212 dcbcdb58 Iustin Pop
         (if oneline then
213 ba6c6006 Iustin Pop
              putStrLn $ formatOneline 0 0 0
214 dcbcdb58 Iustin Pop
          else
215 dcbcdb58 Iustin Pop
              printf "Cluster is empty, exiting.\n")
216 dcbcdb58 Iustin Pop
         exitWith ExitSuccess
217 dcbcdb58 Iustin Pop
218 dcbcdb58 Iustin Pop
219 27f96567 Iustin Pop
  unless oneline $ printf "Loaded %d nodes, %d instances\n"
220 e4f08c46 Iustin Pop
             (Container.size nl)
221 e4f08c46 Iustin Pop
             (Container.size il)
222 a0529a64 Iustin Pop
223 d09b6ed3 Iustin Pop
  when (length csf > 0 && not oneline && verbose > 1) $ do
224 a0529a64 Iustin Pop
         printf "Note: Stripping common suffix of '%s' from names\n" csf
225 a0529a64 Iustin Pop
226 e4f08c46 Iustin Pop
  let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
227 7eff5b09 Iustin Pop
  unless (oneline || verbose == 0) $ printf
228 27f96567 Iustin Pop
             "Initial check done: %d bad nodes, %d bad instances.\n"
229 e4f08c46 Iustin Pop
             (length bad_nodes) (length bad_instances)
230 e4f08c46 Iustin Pop
231 e4f08c46 Iustin Pop
  when (length bad_nodes > 0) $ do
232 289c3835 Iustin Pop
         putStrLn "Cluster is not N+1 happy, continuing but no guarantee \
233 289c3835 Iustin Pop
                  \that the cluster will end N+1 happy."
234 e4f08c46 Iustin Pop
235 e4f08c46 Iustin Pop
  when (optShowNodes opts) $
236 e4f08c46 Iustin Pop
       do
237 e4f08c46 Iustin Pop
         putStrLn "Initial cluster status:"
238 e4f08c46 Iustin Pop
         putStrLn $ Cluster.printNodes ktn nl
239 e4f08c46 Iustin Pop
240 e4f08c46 Iustin Pop
  let ini_cv = Cluster.compCV nl
241 e4f08c46 Iustin Pop
      ini_tbl = Cluster.Table nl il ini_cv []
242 b0517d61 Iustin Pop
      min_cv = optMinScore opts
243 b0517d61 Iustin Pop
244 b0517d61 Iustin Pop
  when (ini_cv < min_cv) $ do
245 b0517d61 Iustin Pop
         (if oneline then
246 ba6c6006 Iustin Pop
              putStrLn $ formatOneline ini_cv 0 ini_cv
247 b0517d61 Iustin Pop
          else printf "Cluster is already well balanced (initial score %.6g,\n\
248 b0517d61 Iustin Pop
                      \minimum score %.6g).\nNothing to do, exiting\n"
249 b0517d61 Iustin Pop
                      ini_cv min_cv)
250 b0517d61 Iustin Pop
         exitWith ExitSuccess
251 b0517d61 Iustin Pop
252 d09b6ed3 Iustin Pop
  unless oneline (if verbose > 2 then
253 7eff5b09 Iustin Pop
                      printf "Initial coefficients: overall %.8f, %s\n"
254 7eff5b09 Iustin Pop
                      ini_cv (Cluster.printStats nl)
255 7eff5b09 Iustin Pop
                  else
256 7eff5b09 Iustin Pop
                      printf "Initial score: %.8f\n" ini_cv)
257 e4f08c46 Iustin Pop
258 27f96567 Iustin Pop
  unless oneline $ putStrLn "Trying to minimize the CV..."
259 7dfaafb1 Iustin Pop
  let mlen_fn = maximum . (map length) . snd . unzip
260 7dfaafb1 Iustin Pop
      imlen = mlen_fn kti
261 7dfaafb1 Iustin Pop
      nmlen = mlen_fn ktn
262 7dfaafb1 Iustin Pop
263 7dfaafb1 Iustin Pop
  (fin_tbl, cmd_strs) <- iterateDepth ini_tbl (optMaxLength opts)
264 b0517d61 Iustin Pop
                         ktn kti nmlen imlen [] oneline min_cv
265 e4f08c46 Iustin Pop
  let (Cluster.Table fin_nl _ fin_cv fin_plc) = fin_tbl
266 e4f08c46 Iustin Pop
      ord_plc = reverse fin_plc
267 7eff5b09 Iustin Pop
      sol_msg = if null fin_plc
268 7eff5b09 Iustin Pop
                then printf "No solution found\n"
269 d09b6ed3 Iustin Pop
                else (if verbose > 2
270 7eff5b09 Iustin Pop
                      then printf "Final coefficients:   overall %.8f, %s\n"
271 7eff5b09 Iustin Pop
                           fin_cv (Cluster.printStats fin_nl)
272 7eff5b09 Iustin Pop
                      else printf "Cluster score improved from %.8f to %.8f\n"
273 7eff5b09 Iustin Pop
                           ini_cv fin_cv
274 7eff5b09 Iustin Pop
                     )
275 e4f08c46 Iustin Pop
276 7eff5b09 Iustin Pop
  unless oneline $ putStr sol_msg
277 7eff5b09 Iustin Pop
278 7eff5b09 Iustin Pop
  unless (oneline || verbose == 0) $
279 7eff5b09 Iustin Pop
         printf "Solution length=%d\n" (length ord_plc)
280 e4f08c46 Iustin Pop
281 e0eb63f0 Iustin Pop
  let cmd_data = Cluster.formatCmds . reverse $ cmd_strs
282 e0eb63f0 Iustin Pop
283 e0eb63f0 Iustin Pop
  when (isJust $ optShowCmds opts) $
284 e4f08c46 Iustin Pop
       do
285 e0eb63f0 Iustin Pop
         let out_path = fromJust $ optShowCmds opts
286 e4f08c46 Iustin Pop
         putStrLn ""
287 e0eb63f0 Iustin Pop
         (if out_path == "-" then
288 e0eb63f0 Iustin Pop
              printf "Commands to run to reach the above solution:\n%s"
289 e0eb63f0 Iustin Pop
                     (unlines . map ("  " ++) .
290 e0eb63f0 Iustin Pop
                      filter (/= "check") .
291 e0eb63f0 Iustin Pop
                      lines $ cmd_data)
292 e0eb63f0 Iustin Pop
          else do
293 e0eb63f0 Iustin Pop
            writeFile out_path (CLI.shTemplate ++ cmd_data)
294 e0eb63f0 Iustin Pop
            printf "The commands have been written to file '%s'\n" out_path)
295 e0eb63f0 Iustin Pop
296 e4f08c46 Iustin Pop
  when (optShowNodes opts) $
297 e4f08c46 Iustin Pop
       do
298 e4f08c46 Iustin Pop
         let (orig_mem, orig_disk) = Cluster.totalResources nl
299 e4f08c46 Iustin Pop
             (final_mem, final_disk) = Cluster.totalResources fin_nl
300 e4f08c46 Iustin Pop
         putStrLn ""
301 e4f08c46 Iustin Pop
         putStrLn "Final cluster status:"
302 e4f08c46 Iustin Pop
         putStrLn $ Cluster.printNodes ktn fin_nl
303 d09b6ed3 Iustin Pop
         when (verbose > 3) $
304 7eff5b09 Iustin Pop
              do
305 7eff5b09 Iustin Pop
                printf "Original: mem=%d disk=%d\n" orig_mem orig_disk
306 7eff5b09 Iustin Pop
                printf "Final:    mem=%d disk=%d\n" final_mem final_disk
307 ba6c6006 Iustin Pop
  when oneline $
308 ba6c6006 Iustin Pop
         putStrLn $ formatOneline ini_cv (length ord_plc) fin_cv