{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Util (
    relativeDirFromPieces,
    defaultMkRedirect,
    replace,
    remove,
    dropLastIfNull,
) where
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as S8
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import WaiAppStatic.Types
replace :: Eq a => a -> b -> [(a, b)] -> [(a, b)]
replace :: forall a b. Eq a => a -> b -> [(a, b)] -> [(a, b)]
replace a
k b
v [] = [(a
k, b
v)]
replace a
k b
v ((a, b)
x : [(a, b)]
xs)
    | (a, b) -> a
forall a b. (a, b) -> a
fst (a, b)
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
k = (a
k, b
v) (a, b) -> [(a, b)] -> [(a, b)]
forall a. a -> [a] -> [a]
: [(a, b)]
xs
    | Bool
otherwise = (a, b)
x (a, b) -> [(a, b)] -> [(a, b)]
forall a. a -> [a] -> [a]
: a -> b -> [(a, b)] -> [(a, b)]
forall a b. Eq a => a -> b -> [(a, b)] -> [(a, b)]
replace a
k b
v [(a, b)]
xs
remove :: Eq a => a -> [(a, b)] -> [(a, b)]
remove :: forall a b. Eq a => a -> [(a, b)] -> [(a, b)]
remove a
_ [] = []
remove a
k ((a, b)
x : [(a, b)]
xs)
    | (a, b) -> a
forall a b. (a, b) -> a
fst (a, b)
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
k = [(a, b)]
xs
    | Bool
otherwise = (a, b)
x (a, b) -> [(a, b)] -> [(a, b)]
forall a. a -> [a] -> [a]
: a -> [(a, b)] -> [(a, b)]
forall a b. Eq a => a -> [(a, b)] -> [(a, b)]
remove a
k [(a, b)]
xs
relativeDirFromPieces :: Pieces -> T.Text
relativeDirFromPieces :: Pieces -> Text
relativeDirFromPieces Pieces
pieces = [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Piece -> Text) -> Pieces -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Piece -> Text
forall a b. a -> b -> a
const Text
"../") (Int -> Pieces -> Pieces
forall a. Int -> [a] -> [a]
drop Int
1 Pieces
pieces) 
defaultMkRedirect :: Pieces -> ByteString -> S8.ByteString
defaultMkRedirect :: Pieces -> ByteString -> ByteString
defaultMkRedirect Pieces
pieces ByteString
newPath
    | ByteString -> Bool
S8.null ByteString
newPath
        Bool -> Bool -> Bool
|| ByteString -> Bool
S8.null ByteString
relDir
        Bool -> Bool -> Bool
|| ByteString -> Char
S8.last ByteString
relDir Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'/'
        Bool -> Bool -> Bool
|| ByteString -> Char
S8.head ByteString
newPath Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'/' =
        ByteString
relDir ByteString -> ByteString -> ByteString
`S8.append` ByteString
newPath
    | Bool
otherwise = ByteString
relDir ByteString -> ByteString -> ByteString
`S8.append` HasCallStack => ByteString -> ByteString
ByteString -> ByteString
S8.tail ByteString
newPath
  where
    relDir :: ByteString
relDir = Text -> ByteString
TE.encodeUtf8 (Pieces -> Text
relativeDirFromPieces Pieces
pieces)
dropLastIfNull :: [Piece] -> [Piece]
dropLastIfNull :: Pieces -> Pieces
dropLastIfNull Pieces
pieces = case Pieces
pieces of
    [Piece -> Text
fromPiece -> Text
""] -> []
    (Piece
a : Pieces
r) -> Piece
a Piece -> Pieces -> Pieces
forall a. a -> [a] -> [a]
: Pieces -> Pieces
dropLastIfNull Pieces
r
    [] -> []