• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

msakai / pseudo-boolean / 130

05 Apr 2025 01:53AM UTC coverage: 91.833% (-0.8%) from 92.655%
130

push

github

web-flow
Merge 0fcff3bfe into 81e38085d

18 of 24 new or added lines in 2 files covered. (75.0%)

2 existing lines in 2 files now uncovered.

506 of 551 relevant lines covered (91.83%)

0.92 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

93.06
/src/Data/PseudoBoolean/ByteStringBuilder.hs
1
{-# OPTIONS_GHC -Wall #-}
2
-----------------------------------------------------------------------------
3
-- |
4
-- Module      :  Data.PseudoBoolean.ByteStringBuilder
5
-- Copyright   :  (c) Masahiro Sakai 2011-2015
6
-- License     :  BSD-style
7
-- 
8
-- Maintainer  :  masahiro.sakai@gmail.com
9
-- Portability :  portable
10
--
11
-----------------------------------------------------------------------------
12

13
module Data.PseudoBoolean.ByteStringBuilder
14
  (
15
  -- * Builder for (Lazy) ByteString generation
16
    opbBuilder
17
  , wboBuilder
18

19
  -- * Lazy ByteString generation
20
  , toOPBByteString
21
  , toWBOByteString
22

23
  -- * File I/O
24
  , writeOPBFile
25
  , writeWBOFile
26
  , hPutOPB
27
  , hPutWBO
28
  ) where
29

30
import qualified Prelude
31
import Prelude hiding (sum)
32
import qualified Data.IntSet as IntSet
33
import qualified Data.Set as Set
34
import Data.List (sortBy)
35
import Data.Maybe (maybeToList)
36
import Data.Monoid hiding (Sum (..))
37
import qualified Data.ByteString.Lazy as BS
38
import Data.ByteString.Builder (Builder, intDec, integerDec, char7, string7, hPutBuilder, toLazyByteString)
39
import Data.Ord
40
import Math.NumberTheory.Logarithms (integerLog2)
41
import System.IO
42
import Data.PseudoBoolean.Types
43

44
-- | A ByteString Builder which renders a OPB format byte-string containing pseudo boolean problem.
45
opbBuilder :: Formula -> Builder
46
opbBuilder opb = (size <> part1 <> part2)
1✔
47
  where
48
    nv = pbNumVars opb
1✔
49
    nc = pbNumConstraints opb
1✔
NEW
50
    neq = length [() | (_lhs, Eq, _rhs) <- pbConstraints opb]
×
51
    intsize = maximum $ 0 :
1✔
52
      [ if tmp == 0 then 0 else 1 + integerLog2 tmp
1✔
53
      | (ts, d) <- [(ts, 0) | ts <- maybeToList (pbObjectiveFunction opb)] ++ [(lhs,rhs) | (lhs,_op,rhs) <- pbConstraints opb]
1✔
54
      , let tmp = abs d + Prelude.sum [abs c | (c,_) <- ts]
1✔
55
      ]
56
    p = pbProducts opb
1✔
57
    np = Set.size p
1✔
58
    sp = Prelude.sum [IntSet.size tm | tm <- Set.toList p]
1✔
59
    size = string7 "* #variable= " <> intDec nv <> string7 " #constraint= " <> intDec nc <> string7 " #equal= " <> intDec neq <> string7 " intsize= " <> intDec intsize
1✔
60
         <> (if np >= 1 then string7 " #product= " <> intDec np <> string7 " sizeproduct= " <> intDec sp else mempty)
1✔
61
         <> char7 '\n'
1✔
62
    part1 = 
1✔
63
      case pbObjectiveFunction opb of
1✔
64
        Nothing -> mempty
1✔
65
        Just o -> string7 "min: " <> showSum o <> string7 ";\n"
1✔
66
    part2 = mconcat $ map showConstraint (pbConstraints opb)
1✔
67

68
-- | A ByteString Builder which renders a WBO format byte-string containing weighted boolean optimization problem.
69
wboBuilder :: SoftFormula -> Builder
70
wboBuilder wbo = size <> part1 <> part2
1✔
71
  where
72
    nv = wboNumVars wbo
1✔
73
    nc = wboNumConstraints wbo
1✔
NEW
74
    neq = length [() | (_, (_lhs, Eq, _rhs)) <- wboConstraints wbo]
×
75
    p = wboProducts wbo
1✔
76
    np = Set.size p
1✔
77
    sp = Prelude.sum [IntSet.size tm | tm <- Set.toList p]
×
78
    mincost =
1✔
79
      case [c | (Just c, _) <- wboConstraints wbo] of
1✔
80
        [] -> 1 -- this should not happen
×
81
        cs -> minimum cs
1✔
82
    maxcost = maximum $ 0 : [c | (Just c, _) <- wboConstraints wbo]
1✔
83
    sumcost = Prelude.sum [c | (Just c, _) <- wboConstraints wbo]
1✔
84
    intsize = maximum $ 0 :
1✔
85
      [ if tmp == 0 then 0 else 1 + integerLog2 tmp
1✔
86
      | (cs, d) <- ([sumcost], 0) : [(map fst lhs, rhs) | (_,(lhs,_op,rhs)) <- wboConstraints wbo]
1✔
87
      , let tmp = abs d + Prelude.sum [abs c | c <- cs]
1✔
88
      ]
89
    size = string7 "* #variable= " <> intDec nv <> string7 " #constraint= " <> intDec nc <> string7 " #equal= " <> intDec neq <> string7 " intsize= " <> intDec intsize
1✔
UNCOV
90
         <> (if np >= 1 then string7 " #product= " <> intDec np <> string7 " sizeproduct= " <> intDec sp else mempty)
×
91
         <> string7 " #soft= " <> intDec (wboNumSoft wbo)
1✔
92
         <> string7 " mincost= " <> integerDec mincost
1✔
93
         <> string7 " maxcost= " <> integerDec maxcost
1✔
94
         <> string7 " sumcost= " <> integerDec sumcost
1✔
95
         <> char7 '\n'
1✔
96
    part1 = 
1✔
97
      case wboTopCost wbo of
1✔
98
        Nothing -> string7 "soft: ;\n"
1✔
99
        Just t -> string7 "soft: " <> integerDec t <> string7 ";\n"
1✔
100
    part2 = mconcat $ map showSoftConstraint (wboConstraints wbo)
1✔
101

102
showSum :: Sum -> Builder
103
showSum = mconcat . map showWeightedTerm
1✔
104

105
showWeightedTerm :: WeightedTerm -> Builder
106
showWeightedTerm (c, lits) = foldr (\f g -> f <> char7 ' ' <> g) mempty (x:xs)
1✔
107
  where
108
    x = if c >= 0 then char7 '+' <> integerDec c else integerDec c
1✔
109
    xs = map showLit $ sortBy (comparing abs) lits
1✔
110

111
showLit :: Lit -> Builder
112
showLit lit = if lit > 0 then v else char7 '~' <> v
1✔
113
  where
114
    v = char7 'x' <> intDec (abs lit)
1✔
115

116
showConstraint :: Constraint -> Builder
117
showConstraint (lhs, op, rhs) =
1✔
118
  showSum lhs <> f op <>  char7 ' ' <> integerDec rhs <> string7 ";\n"
1✔
119
  where
120
    f Eq = char7 '='
1✔
121
    f Ge = string7 ">="
1✔
122

123
showSoftConstraint :: SoftConstraint -> Builder
124
showSoftConstraint (cost, constr) =
1✔
125
  case cost of
1✔
126
    Nothing -> showConstraint constr
1✔
127
    Just c -> char7 '[' <> integerDec c <> string7 "] " <> showConstraint constr
1✔
128

129

130

131
-- | Generate a OPB format byte-string containing pseudo boolean problem.
132
toOPBByteString :: Formula -> BS.ByteString
133
toOPBByteString opb = toLazyByteString (opbBuilder opb)
1✔
134

135
-- | Generate a WBO format byte-string containing weighted boolean optimization problem.
136
toWBOByteString :: SoftFormula -> BS.ByteString
137
toWBOByteString wbo = toLazyByteString (wboBuilder wbo)
1✔
138

139
-- | Output a OPB file containing pseudo boolean problem.
140
writeOPBFile :: FilePath -> Formula -> IO ()
141
writeOPBFile filepath opb = withBinaryFile filepath WriteMode $ \h -> do
1✔
142
  hSetBuffering h (BlockBuffering Nothing)
1✔
143
  hPutOPB h opb
1✔
144

145
-- | Output a WBO file containing weighted boolean optimization problem.
146
writeWBOFile :: FilePath -> SoftFormula -> IO ()
147
writeWBOFile filepath wbo = withBinaryFile filepath WriteMode $ \h -> do
1✔
148
  hSetBuffering h (BlockBuffering Nothing)
1✔
149
  hPutWBO h wbo
1✔
150

151
-- | Output a OPB file to a 'Handle' using 'hPutBuilder'.
152
--
153
-- It is recommended that the 'Handle' is set to binary and
154
-- 'BlockBuffering' mode. See 'hSetBinaryMode' and 'hSetBuffering'.
155
--
156
-- This function is more efficient than 'hPut' . 'toOPBByteString'
157
-- because in many cases no buffer allocation has to be done.
158
hPutOPB :: Handle -> Formula -> IO ()
159
hPutOPB h opb = hPutBuilder h (opbBuilder opb)
1✔
160

161

162
-- | Output a WBO file to a 'Handle' using 'hPutBuilder'.
163
--
164
-- It is recommended that the 'Handle' is set to binary and
165
-- 'BlockBuffering' mode. See 'hSetBinaryMode' and 'hSetBuffering'.
166
--
167
-- This function is more efficient than 'hPut' . 'toWBOByteString'
168
-- because in many cases no buffer allocation has to be done.
169
hPutWBO :: Handle -> SoftFormula -> IO ()
170
hPutWBO h wbo = hPutBuilder h (wboBuilder wbo)
1✔
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2025 Coveralls, Inc