{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} module Dhall.URL where import Data.Text (Text) import Dhall.Syntax (Directory (..), File (..), Scheme (..), URL (..)) renderComponent :: Text -> Text renderComponent :: Text -> Text renderComponent Text component = Text "/" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text component renderQuery :: Text -> Text renderQuery :: Text -> Text renderQuery Text query = Text "?" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text query renderURL :: URL -> Text renderURL :: URL -> Text renderURL URL url = Text schemeText Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text authority Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text pathText Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text queryText where URL {Maybe Text Maybe (Expr Src Import) Text Scheme File authority :: Text scheme :: Scheme path :: File query :: Maybe Text headers :: Maybe (Expr Src Import) scheme :: URL -> Scheme authority :: URL -> Text path :: URL -> File query :: URL -> Maybe Text headers :: URL -> Maybe (Expr Src Import) ..} = URL url File {Text Directory directory :: Directory file :: Text directory :: File -> Directory file :: File -> Text ..} = File path Directory {[Text] components :: [Text] components :: Directory -> [Text] ..} = Directory directory schemeText :: Text schemeText = case Scheme scheme of Scheme HTTP -> Text "http://" Scheme HTTPS -> Text "https://" pathText :: Text pathText = (Text -> Text) -> [Text] -> Text forall m a. Monoid m => (a -> m) -> [a] -> m forall (t :: * -> *) m a. (Foldable t, Monoid m) => (a -> m) -> t a -> m foldMap Text -> Text renderComponent ([Text] -> [Text] forall a. [a] -> [a] reverse [Text] components) Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text -> Text renderComponent Text file queryText :: Text queryText = (Text -> Text) -> Maybe Text -> Text forall m a. Monoid m => (a -> m) -> Maybe a -> m forall (t :: * -> *) m a. (Foldable t, Monoid m) => (a -> m) -> t a -> m foldMap Text -> Text renderQuery Maybe Text query