summaryrefslogtreecommitdiff
path: root/Utility/SRV.hs
blob: 4f2db680b54444bec020439aef9b1e4cad630e29 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
{- SRV record lookup
 -
 - Uses either the ADNS Haskell library, or if it's not installed,
 - the host command.
 -
 - Copyright 2012 Joey Hess <joey@kitenet.net>
 -
 - Licensed under the GNU GPL version 3 or higher.
 -}

{-# LANGUAGE CPP #-}

module Utility.SRV (
	mkSRVTcp,
	mkSRV,
	lookupSRV,
) where

import qualified Build.SysConfig
import Utility.Process
import Utility.Exception
import Utility.PartialPrelude

import Network
import Data.Function
import Data.List
import Control.Applicative
import Data.Maybe

#ifdef WITH_ADNS
import ADNS.Resolver
import Data.Either
#endif

newtype SRV = SRV String
	deriving (Show, Eq)

type HostPort = (HostName, PortID)

mkSRV :: String -> String -> HostName -> SRV
mkSRV transport protocol host = SRV $ concat
	["_", protocol, "._", transport, ".", host]

mkSRVTcp :: String -> HostName -> SRV
mkSRVTcp = mkSRV "tcp"

{- Returns an ordered list, with highest priority hosts first.
 -
 - On error, returns an empty list. -}
lookupSRV :: SRV -> IO [HostPort]
#ifdef WITH_ADNS
lookupSRV srv = initResolver [] $ \resolver -> do
	r <- catchDefaultIO (Right []) $
		resolveSRV resolver srv
	return $ either (\_ -> []) id r
#else
lookupSRV = lookupSRVHost
#endif

lookupSRVHost :: SRV -> IO [HostPort]
lookupSRVHost (SRV srv)
	| Build.SysConfig.host = catchDefaultIO [] $ 
		parseSrvHost <$> readProcessEnv "host" ["-t", "SRV", "--", srv]
			-- clear environment, to avoid LANG affecting output
			(Just [])
	| otherwise = return []

parseSrvHost :: String -> [HostPort]
parseSrvHost = map snd . reverse . sortBy cost . catMaybes . map parse . lines
	where
		cost = compare `on` fst
		parse l = case words l of
			[_, _, _, _, priority, weight, sport, hostname] -> do
				let v = readish sport :: Maybe Int
				case v of
					Nothing -> Nothing
					Just port -> Just
						( (priority, weight)
						, (hostname, PortNumber $ fromIntegral port)
						)
			_ -> Nothing