summaryrefslogtreecommitdiffhomepage
path: root/Network
diff options
context:
space:
mode:
authorGravatar Kazu Yamamoto <kazu@iij.ad.jp>2010-05-07 15:25:20 +0900
committerGravatar Kazu Yamamoto <kazu@iij.ad.jp>2010-05-07 15:25:20 +0900
commit907f236b1fa936493eeb21c054b439483a34e8ae (patch)
treea2a64d31e42ee34fbbcdb8d5d3d3cb329e9ab25c /Network
parentf058a1be787eaadc41f53785cadb058edf20762b (diff)
hlint.
Diffstat (limited to 'Network')
-rw-r--r--Network/DNS/Internal.hs7
-rw-r--r--Network/DNS/Lookup.hs2
-rw-r--r--Network/DNS/Response.hs15
-rw-r--r--Network/DNS/StateBinary.hs2
4 files changed, 14 insertions, 12 deletions
diff --git a/Network/DNS/Internal.hs b/Network/DNS/Internal.hs
index 0f53b80..ccc8cf7 100644
--- a/Network/DNS/Internal.hs
+++ b/Network/DNS/Internal.hs
@@ -3,6 +3,7 @@ module Network.DNS.Internal where
import qualified Data.ByteString.Lazy.Char8 as L
import Data.Char
import Data.IP
+import Data.Maybe
----------------------------------------------------------------
@@ -37,10 +38,10 @@ rookup key ((x,y):xys)
| otherwise = rookup key xys
intToType :: Int -> TYPE
-intToType n = maybe (UNKNOWN n) id $ rookup n rrDB
+intToType n = fromMaybe (UNKNOWN n) $ rookup n rrDB
typeToInt :: TYPE -> Int
typeToInt (UNKNOWN x) = x
-typeToInt t = maybe 0 id $ lookup t rrDB
+typeToInt t = fromMaybe 0 $ lookup t rrDB
toType :: String -> TYPE
toType = read . map toUpper
@@ -105,7 +106,7 @@ data Question = Question {
Making "Question".
-}
makeQuestion :: Domain -> TYPE -> Question
-makeQuestion dom typ = Question dom typ
+makeQuestion = Question
----------------------------------------------------------------
diff --git a/Network/DNS/Lookup.hs b/Network/DNS/Lookup.hs
index 5f27fa5..beb682f 100644
--- a/Network/DNS/Lookup.hs
+++ b/Network/DNS/Lookup.hs
@@ -67,7 +67,7 @@ lookupXviaMX rlv dom func = do
maybe (return Nothing) lookup' mdps
where
lookup' dps = do
- as <- catMaybes <$> mapM func (map fst dps)
+ as <- catMaybes <$> mapM (func . fst) dps
case as of
[] -> return Nothing
ass -> return $ Just (concat ass)
diff --git a/Network/DNS/Response.hs b/Network/DNS/Response.hs
index 898b838..c62f497 100644
--- a/Network/DNS/Response.hs
+++ b/Network/DNS/Response.hs
@@ -5,23 +5,24 @@ import Data.Bits
import qualified Data.ByteString.Lazy.Char8 as L
import Data.Char
import Data.IP
-import Network.DNS.StateBinary
+import Data.Maybe
import Network.DNS.Internal
+import Network.DNS.StateBinary
----------------------------------------------------------------
parseResponse :: L.ByteString -> DNSFormat
-parseResponse bs = runSGet decodeResponse bs
+parseResponse = runSGet decodeResponse
----------------------------------------------------------------
decodeResponse :: SGet DNSFormat
decodeResponse = do
hd <- decodeHeader
- DNSFormat hd <$> (decodeQueries $ qdCount hd)
- <*> (decodeRRs $ anCount hd)
- <*> (decodeRRs $ nsCount hd)
- <*> (decodeRRs $ arCount hd)
+ DNSFormat hd <$> decodeQueries (qdCount hd)
+ <*> decodeRRs (anCount hd)
+ <*> decodeRRs (nsCount hd)
+ <*> decodeRRs (arCount hd)
----------------------------------------------------------------
@@ -136,7 +137,7 @@ decodeDomain = do
then do
d <- getInt8
let offset = n * 256 + d
- maybe (error $ "decodeDomain: " ++ show offset) id <$> pop offset
+ fromMaybe (error $ "decodeDomain: " ++ show offset) <$> pop offset
else do
hs <- decodeString n
ds <- decodeDomain
diff --git a/Network/DNS/StateBinary.hs b/Network/DNS/StateBinary.hs
index 5e27b30..ffbf728 100644
--- a/Network/DNS/StateBinary.hs
+++ b/Network/DNS/StateBinary.hs
@@ -92,7 +92,7 @@ getNByteString len = lift . getLazyByteString . fromIntegral $ len
----------------------------------------------------------------
push :: Int -> Domain -> SGet ()
-push n d = modify (\m -> IM.insert n d m)
+push n d = modify (IM.insert n d)
pop :: Int -> SGet (Maybe Domain)
pop n = IM.lookup n <$> get