{-# LANGUAGE OverloadedStrings, UnicodeSyntax, Safe, CPP #-}

module Network.HTTP.Link.Writer (
  writeLink
, writeLinkHeader
) where

import           Data.Text hiding (map)
#if !MIN_VERSION_base(4,8,0)
import           Data.Monoid (mconcat)
#endif
import           Network.URI
import           Network.HTTP.Link.Types

writeParamKey  LinkParam  Text
writeParamKey :: LinkParam -> Text
writeParamKey LinkParam
Rel = Text
"rel"
writeParamKey LinkParam
Anchor = Text
"anchor"
writeParamKey LinkParam
Rev = Text
"rev"
writeParamKey LinkParam
Hreflang = Text
"hreflang"
writeParamKey LinkParam
Media = Text
"media"
writeParamKey LinkParam
Title = Text
"title"
writeParamKey LinkParam
Title' = Text
"title*"
writeParamKey LinkParam
ContentType = Text
"type"
writeParamKey (Other Text
t) = Text
t

writeParam  (LinkParam, Text)  Text
writeParam :: (LinkParam, Text) -> Text
writeParam (LinkParam
t, Text
v) = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [Text
"; ", LinkParam -> Text
writeParamKey LinkParam
t, Text
"=\"", Text -> Text
escPar Text
v, Text
"\""]
  where escPar :: Text -> Text
escPar = String -> Text
pack (String -> Text) -> (Text -> String) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> String
escapeURIString (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'"') (String -> String) -> (Text -> String) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack
        -- maybe URI escaping is not what we should do here? eh, whatever

writeLink  (IsURI uri)  Link uri  Text
writeLink :: Link uri -> Text
writeLink (Link uri
u [(LinkParam, Text)]
ps) = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text
"<", uri -> Text
forall uri. IsURI uri => uri -> Text
uriToText uri
u, Text
">"] [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ ((LinkParam, Text) -> Text) -> [(LinkParam, Text)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (LinkParam, Text) -> Text
writeParam [(LinkParam, Text)]
ps

writeLinkHeader  (IsURI uri)  [Link uri]  Text
writeLinkHeader :: [Link uri] -> Text
writeLinkHeader = Text -> [Text] -> Text
intercalate Text
", " ([Text] -> Text) -> ([Link uri] -> [Text]) -> [Link uri] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Link uri -> Text) -> [Link uri] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Link uri -> Text
forall uri. IsURI uri => Link uri -> Text
writeLink