Disclaimer: It's literally the second time I write in Haskell.
The purpose of this module is to provide some basic operations with IP addresses (and networks).
At the moment I only implemented the successor
operation, that returns a next address in the range if it exists.
Eg: for 192.168.1.1
in 192.168.1.0/24
it would return Maybe 192.168.1.1
And for 192.168.1.255
(which is the last valid IP address in the given network) it would return Nothing
.
module Main where
import Data.IP (IPv4, AddrRange(addr), fromIPv4, toIPv4, isMatchedTo, makeAddrRange)
import Data.Bits (shiftL, shiftR, (.|.), (.&.))
import Data.List (foldl')
import Text.Read (readMaybe)
import qualified Safe as S
parse :: String -> Maybe IPv4
parse = readMaybe
toInt :: IPv4 -> Int
toInt i = foldl' accum 0 (fromIPv4 i)
where accum a v = (a `shiftL` 8) .|. v
fromInt :: Int -> IPv4
fromInt i = toIPv4 $ map (\s -> (i `shiftR` s) .&. 0xff) [24, 16, 8, 0]
addressesInNetwork :: AddrRange IPv4 -> [IPv4]
addressesInNetwork i = takeWhile (`isMatchedTo` i) adds
where net = toInt $ addr i
adds = map (\s -> fromInt $ net + s) [0..]
successor :: Int -> IPv4 -> Maybe IPv4
successor r a = S.headMay $ dropWhile (<= a) $ addressesInNetwork $ makeAddrRange a r
net24 :: IPv4 -> Maybe IPv4
net24 = successor 24
main::IO()
main = print $ parse "192.168.1.201" >>= net24
What I don't like: it just looks terrible. I look on it and see Perl, not Haskell.
Have I done something idiomatically wrong or my sense of beauty is broken?
2 Answers 2
I think what you've missed is the Enum
instance for the IPv4
datatype from iproute
. Using methods from Enum
and Bounded
you can eliminate the use of Data.Bits
in your code.
Because IPv4
is Enum
, your toInt
method is just fromEnum :: (Enum a) => a -> Int
. And similarly your fromInt
is toEnum
.
addressesInNetwork
is largely the same logic, you just let someone else do all the work.
addressesInNetwork :: AddrRange IPv4 -> [IPv4]
addressesInNetwork range = takeWhile (`isMatchedTo` range) [low..]
where
(low, _) = addrRangePair range
I would use addrRangePair
instead of the addr
field accessor for two reasons. First, addr
doesn't show up in the Haddock documentation for Data.IP
which is a bit confusing. Second, on the off-chance that the author of iproute
begins hiding the constructors of AddrRange
from export (which is very common practice in Haskell so that library authors can change implementations without breaking users' code) you'll be safe from breaking changes.
Knowing the Enum
instance and available Data.IP
functions, you can now write a clearer version of successor
. Unfortunately we have to be a bit cautious of bounds, Enum
throws an exception if you try to get the successor of maxBound
, but it's not too bad.
successor :: AddrRange IPv4 -> IPv4 -> Maybe IPv4
successor range ip | ip == maxBound = Nothing
| succ ip `isMatchedTo` range = Just $ succ ip
| otherwise = Nothing
Notice I changed the type signature of your function to take an AddrRange
instead of a mask length. This is kind of a separation of concerns issue, successor
doesn't care about the mask length, what matters is whether an IP falls within the range it defines. So net24
would be implemented as—
net24 :: IPv4 -> Maybe IPv4
net24 ip = successor (makeAddrRange ip 24) ip
(That's kind of a strange name though, maybe successorMask24
instead?)
-
\$\begingroup\$ "That's kind of a strange name though" --- It's actually an artifact from experiments, that I decided to not drop :-) \$\endgroup\$zerkms– zerkms2015年04月04日 21:21:55 +00:00Commented Apr 4, 2015 at 21:21
-
\$\begingroup\$ After reworking my code I can tell - it's a super valuable answer (I don't have anything "own" left in my code though, but it's okay) \$\endgroup\$zerkms– zerkms2015年04月04日 21:50:39 +00:00Commented Apr 4, 2015 at 21:50
-
1\$\begingroup\$ Haha well the easiest code to maintain is no code at all. ;-) \$\endgroup\$bisserlis– bisserlis2015年04月04日 22:13:25 +00:00Commented Apr 4, 2015 at 22:13
You can add a digit to the integer converted by toInt
and then convert it back into an IPv4. I couldn't find any generic library in haskell to do this. The one closest to this was showIntAtBase
in Numeric. I modified it
showIntAtBaseGeneric base toChr concat n0 r0
| base <= 1 = error ("Numeric.showIntAtBase: applied to unsupported base " ++ show base)
| n0 < 0 = error ("Numeric.showIntAtBase: applied to negative number " ++ show n0)
| otherwise = showIt (quotRem n0 base) r0
where
showIt (n,d) r = seq c $ -- stricter than necessary
case n of
0 -> r'
_ -> showIt (quotRem n base) r'
where
c = toChr (fromIntegral d)
r' = concat c r
Now:
λ> let foo = succ $ toInt (toIPv4 [192,0,2,1])
λ> showIntAtBaseGeneric 256 id (:) foo []
[192,0,2,2]
You can then use the libraries to convert into an IPv4 and check if this is in the valid range (and accordingly return Nothing or Just IPv4).
Note: showIntAtBase
can be implemented using showIntAtBaseGeneric
trivially (as shown below). I don't know if this would qualify as useful though :/
showIntAtBase :: (Integral a, Show a) => a -> (Int -> Char) -> a -> ShowS
showIntAtBase base toChr n0 r0 = showIntAtBaseGeneric base toChr (:) n0 r0