Skip to content

Commit

Permalink
apply hlint
Browse files Browse the repository at this point in the history
  • Loading branch information
bravit committed Jan 17, 2019
1 parent c7c8ec1 commit e60395e
Show file tree
Hide file tree
Showing 3 changed files with 7 additions and 7 deletions.
4 changes: 2 additions & 2 deletions ipgen/GenIP.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ genIPComponents = Gen.list (Range.singleton 4) genOctet
where genOctet = Gen.word8 Range.linearBounded

genIPString :: Gen String
genIPString = concat . intersperse "." . map show <$> genIPComponents
genIPString = intercalate "." . map show <$> genIPComponents

genIPRange :: Gen IPRange
genIPRange = do
Expand All @@ -27,7 +27,7 @@ genIPRange = do

genInvalidIPRange :: Gen IPRange
genInvalidIPRange = do
(IP ip1) <- Gen.filter (> (IP minBound)) genIP
(IP ip1) <- Gen.filter (> IP minBound) genIP
ip2 <- Gen.word32 (Range.linear minBound (ip1 - 1))
pure $ IPRange (IP ip1) (IP ip2)

Expand Down
4 changes: 2 additions & 2 deletions iplookup/IPTypes.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,14 @@
module IPTypes where

import Data.Word
import Data.List (intersperse)
import Data.List (intercalate)
import Control.Exception.Safe

newtype IP = IP {unIP :: Word32}
deriving (Eq, Ord)

instance Show IP where
show (IP ip) = concat $ intersperse "." $ map show [b4,b3,b2,b1]
show (IP ip) = intercalate "." $ map show [b4,b3,b2,b1]
where
(ip1, b1) = ip `divMod` 256
(ip2, b2) = ip1 `divMod` 256
Expand Down
6 changes: 3 additions & 3 deletions iplookup/ParseIP.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ module ParseIP where
import Data.Word
import Data.Bits (shiftL, toIntegralSized)
import Data.List.Split (splitOn)
import Data.Maybe (catMaybes)
import Data.Maybe (mapMaybe)
import Control.Applicative
import Control.Monad
import Safe
Expand Down Expand Up @@ -71,7 +71,7 @@ parseIPRanges = fmap IPRangeDB . mapM parseLine . zip [1..] . lines
Just ipr -> Right ipr

parseValidIPs :: String -> [IP]
parseValidIPs = catMaybes . map parseIP . lines
parseValidIPs = mapMaybe parseIP . lines

parseValidIPRanges :: String -> IPRangeDB
parseValidIPRanges = IPRangeDB . catMaybes . map parseIPRange . lines
parseValidIPRanges = IPRangeDB . mapMaybe parseIPRange . lines

0 comments on commit e60395e

Please sign in to comment.