-- This file is part of htalkat -- Copyright (C) 2021 Martin Bays -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of version 3 of the GNU General Public License as -- published by the Free Software Foundation, or any later version. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see http://www.gnu.org/licenses/. {-# LANGUAGE Safe #-} module Host where import Control.Monad (msum) import Data.List (elemIndices) import Data.Maybe (fromMaybe) import Safe (lastMay, readMay) data Host = Host {hostName :: String, hostPort :: Int} deriving (Eq,Ord,Show) defaultTalkatPort :: Int defaultTalkatPort = 5518 showHost :: Host -> String showHost (Host name port) = name ++ (if port == defaultTalkatPort then "" else ":" ++ show port) parseHost :: String -> Maybe Host parseHost s = msum [ (`Host` defaultTalkatPort) <$> decodeIPv6 s , do i <- lastMay $ elemIndices ':' s let (h, ':':portStr) = splitAt i s h' = fromMaybe h $ decodeIPv6 h Host h' <$> readMay portStr , pure $ Host s defaultTalkatPort ] where decodeIPv6 :: String -> Maybe String decodeIPv6 ('[':rest) | Just ']' <- lastMay rest = Just $ init rest decodeIPv6 _ = Nothing