]> gitweb.michael.orlitzky.com - dead/harbl.git/blob - harbl/src/Network/DNS/RBL/Weight.hs
Separate the Network.DNS.RBL.Weight module and fix the doctests.
[dead/harbl.git] / harbl / src / Network / DNS / RBL / Weight.hs
1 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
2
3 -- | The 'Weight' type, its instances, and a Parsec parser to parse
4 -- one off the end of a 'Site'.
5 --
6 -- This is a simple newtype wrapper around an 'Int', meant to be
7 -- used wherever a weight or an RBL score is intended (to prevent
8 -- integer mixups). For example, the RBLs are all weighted with
9 -- 'Weight's, and when a user supplied a \"badness\" threshold, it
10 -- will be as a 'Weight' as well. The two are then comparable but
11 -- not with other 'Int's.
12 --
13 module Network.DNS.RBL.Weight (
14 Weight(..),
15 weight )
16 where
17
18 import Text.Parsec (
19 (<|>),
20 char,
21 digit,
22 many1,
23 option,
24 try,
25 unexpected )
26 import Text.Parsec.String ( Parser )
27 import Text.Read ( readMaybe )
28
29 import Network.DNS.RBL.Pretty ( Pretty(..) )
30
31
32 -- | The 'Weight' wrapper around an 'Int. We use
33 -- GeneralizedNewtypeDeriving to derive num automatically (so that we
34 -- can sum these things).
35 --
36 -- ==== _Examples_
37 --
38 -- >>> let w1 = Weight 1
39 -- >>> w1
40 -- Weight 1
41 -- >>> let w2 = Weight 1
42 -- >>> w1 == w2
43 -- True
44 -- >>> let w3 = Weight 2
45 -- >>> w1 == w3
46 -- False
47 -- >>> sum [w1, w2, w3]
48 -- Weight 4
49 --
50 newtype Weight = Weight Int deriving (Eq, Num, Show)
51
52
53 -- | Pretty-print a 'Weight'. This just shows/prints the underlying 'Int'.
54 --
55 -- ==== _Examples_
56 --
57 -- >>> pretty_print $ Weight 17
58 -- 17
59 --
60 instance Pretty Weight where
61 pretty_show (Weight w) = show w
62
63
64 -- | Parse the weight multiplier off the end of an input 'Site'. This
65 -- expects there to be a \"multiplier\" character (an asterisk)
66 -- before the integral weight.
67 --
68 -- ==== _Examples_
69 --
70 -- >>> import Text.Parsec ( parseTest )
71 --
72 -- Negative, zero, and positive integers are all supported:
73 --
74 -- >>> parseTest weight "*-5"
75 -- Weight (-5)
76 --
77 -- >>> parseTest weight "*0"
78 -- Weight 0
79 --
80 -- >>> parseTest weight "*17"
81 -- Weight 17
82 --
83 -- If the weight is empty, it defaults to @1@:
84 --
85 -- >>> parseTest weight ""
86 -- Weight 1
87 --
88 -- The default is used whenever parsing fails:
89 --
90 -- >>> parseTest weight "*hello"
91 -- Weight 1
92 --
93 -- The 'Pretty' instance works as intended:
94 --
95 -- >>> import Text.Parsec ( parse )
96 -- >>> pretty_print $ parse weight "" "*3"
97 -- 3
98 --
99 weight :: Parser Weight
100 weight = try parse_weight <|> return (Weight 1)
101 where
102 parse_weight = do
103 _ <- char '*'
104 sign <- (char '-') <|> (option '+' (char '+'))
105 w <- many1 digit
106 case ( readMaybe w :: Maybe Int ) of
107 -- If "many1 digit" gives us a list of digits, we should be able
108 -- to convert that to an Int! It will overflow rather than fail
109 -- if the input is too big/small, so it should really always
110 -- succeed.
111 Nothing -> unexpected "weight: readMaybe failed on a sequence of digits!"
112 Just k -> return $ Weight (if sign == '-' then negate k else k)