Created
November 1, 2011 08:13
-
-
Save jkff/1330135 to your computer and use it in GitHub Desktop.
Haskell IP filter
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Main where | |
import qualified Data.ByteString.Lazy.Char8 as B | |
import System.Environment (getArgs) | |
import Data.Word | |
import Data.List | |
import Data.Array.Base (unsafeAt) | |
import Data.Array.Unboxed | |
import Data.Monoid | |
import Blaze.ByteString.Builder | |
import Blaze.ByteString.Builder.Char8 | |
newtype IP = IP { ipValue :: Word32 } deriving (Ord, Eq) | |
toSplitPoints Nothing [] = [] | |
toSplitPoints (Just e) [] = [e] | |
toSplitPoints Nothing ((a,b):ps) = a:toSplitPoints (Just b) ps | |
toSplitPoints (Just e) ((a,b):ps) = if a > e then e:a:toSplitPoints (Just b) ps else toSplitPoints (Just (max e b)) ps | |
bsearch :: (Int -> Bool) -> (Int, Int) -> Maybe Int | |
bsearch p (a,b) | a >= b = if p a then Just a else Nothing | |
| otherwise = let mid = a + (b-a)`div`2 in if p mid then bsearch p (a,mid) else bsearch p (mid+1,b) | |
parseFilter ips = let ips' = toSplitPoints Nothing (sort ips) | |
n = length ips' | |
arr = listArray (0,n-1) (map ipValue ips') :: UArray Int Word32 | |
in \(IP ip) -> maybe False odd $ bsearch (\i -> unsafeAt arr i > ip) (0,n-1) | |
parseIPPair s = let [a,b] = B.split ',' s in (parseIP a, parseIP b) | |
parseIP s = IP (((fromIntegral a*256+fromIntegral b)*256+fromIntegral c)*256+fromIntegral d) | |
where Just (a,_bcd) = B.readInt s | |
Just (b,_cd) = B.readInt (B.tail _bcd) | |
Just (c,_d) = B.readInt (B.tail _cd) | |
Just (d,_) = B.readInt (B.tail _d) | |
dot = fromChar '.' | |
putIP (IP abcd) = writeInt a <> dot <> writeInt b <> dot <> writeInt c <> dot <> writeInt d | |
where (abc,d) = abcd `divMod` 256 | |
(ab,c) = abc `divMod` 256 | |
(a,b) = ab `divMod` 256 | |
writeInt x = fromShow x | |
(<>) = mappend | |
main = do | |
[filterFile, sampleFile] <- getArgs | |
filterF <- B.readFile filterFile >>= return . parseFilter . map parseIPPair . B.lines | |
samples <- B.readFile sampleFile >>= return . map parseIP . B.lines | |
B.putStr . toLazyByteString . mconcat . intersperse (fromChar '\n') . map putIP . filter filterF $ samples |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment