-- This file is part of Diohsc -- Copyright (C) 2020 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 Request where import Data.List (elemIndices) import Data.Maybe (fromMaybe) import Safe (lastMay, readMay) import URI (URI, escapePathString, nullUri, parseAbsoluteUri) data Host = Host {hostName :: String, hostPort :: Int} deriving (Eq,Ord,Show) showHost :: Host -> String showHost (Host name port) = name ++ ":" ++ show port parseHost :: String -> Maybe Host parseHost s = do i <- lastMay $ elemIndices ':' s (hostname, ':':portStr) <- return $ splitAt i s Host hostname <$> readMay portStr data Request = NetworkRequest {requestHost :: Host, networkRequestUri :: URI} | LocalFileRequest {requestPath :: FilePath} deriving (Eq,Ord,Show) requestUri :: Request -> URI requestUri (NetworkRequest _ uri) = uri requestUri (LocalFileRequest abspath) = fromMaybe nullUri . parseAbsoluteUri $ "file://" <> escapePathString abspath