{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module WaiAppStatic.Storage.Embedded.TH (
    Etag,
    EmbeddableEntry (..),
    mkSettings,
) where
import Codec.Compression.GZip (compress)
import qualified Data.ByteString as B
import Data.ByteString.Builder.Extra (byteStringInsert)
import qualified Data.ByteString.Lazy as BL
import Data.ByteString.Unsafe (unsafePackAddressLen)
import Data.Either (lefts, rights)
import GHC.Exts (Int (..))
import Language.Haskell.TH
import Network.Mime (MimeType, defaultMimeLookup)
import System.IO.Unsafe (unsafeDupablePerformIO)
import WaiAppStatic.Storage.Filesystem (defaultWebAppSettings)
import WaiAppStatic.Types
#if !MIN_VERSION_template_haskell(2, 8, 0)
import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy.Char8 as BL8
#endif
import qualified Data.HashMap.Strict as M
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Network.Wai as W
type Etag = T.Text
data EmbeddableEntry = EmbeddableEntry
    { EmbeddableEntry -> Text
eLocation :: T.Text
    
    
    
    , EmbeddableEntry -> ByteString
eMimeType :: MimeType
    
    , EmbeddableEntry -> Either (Text, ByteString) ExpQ
eContent :: Either (Etag, BL.ByteString) ExpQ
    
    
    
    
    
    
    }
data EmbeddedEntry = EmbeddedEntry
    { EmbeddedEntry -> Text
embLocation :: !T.Text
    , EmbeddedEntry -> ByteString
embMime :: !MimeType
    , EmbeddedEntry -> ByteString
embEtag :: !B.ByteString
    , EmbeddedEntry -> Bool
embCompressed :: !Bool
    , EmbeddedEntry -> ByteString
embContent :: !B.ByteString
    }
data ReloadEntry = ReloadEntry
    { ReloadEntry -> Text
reloadLocation :: !T.Text
    , ReloadEntry -> ByteString
reloadMime :: !MimeType
    , ReloadEntry -> IO (Text, ByteString)
reloadContent :: IO (T.Text, BL.ByteString)
    }
bytestringE :: B.ByteString -> ExpQ
#if MIN_VERSION_template_haskell(2, 8, 0)
bytestringE :: ByteString -> ExpQ
bytestringE ByteString
b = [| unsafeDupablePerformIO (unsafePackAddressLen (I# $ExpQ
lenE) $ExpQ
ctE) |]
    where
        lenE :: ExpQ
lenE = Lit -> ExpQ
forall (m :: * -> *). Quote m => Lit -> m Exp
litE (Lit -> ExpQ) -> Lit -> ExpQ
forall a b. (a -> b) -> a -> b
$ Integer -> Lit
intPrimL (Integer -> Lit) -> Integer -> Lit
forall a b. (a -> b) -> a -> b
$ Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
b
        ctE :: ExpQ
ctE = Lit -> ExpQ
forall (m :: * -> *). Quote m => Lit -> m Exp
litE (Lit -> ExpQ) -> Lit -> ExpQ
forall a b. (a -> b) -> a -> b
$ [Word8] -> Lit
stringPrimL ([Word8] -> Lit) -> [Word8] -> Lit
forall a b. (a -> b) -> a -> b
$ ByteString -> [Word8]
B.unpack ByteString
b
#else
bytestringE b =
    [| B8.pack $s |]
  where
    s = litE $ stringL $ B8.unpack b
#endif
bytestringLazyE :: BL.ByteString -> ExpQ
#if MIN_VERSION_template_haskell(2, 8, 0)
bytestringLazyE :: ByteString -> ExpQ
bytestringLazyE ByteString
b = [| unsafeDupablePerformIO (unsafePackAddressLen (I# $ExpQ
lenE) $ExpQ
ctE) |]
    where
        lenE :: ExpQ
lenE = Lit -> ExpQ
forall (m :: * -> *). Quote m => Lit -> m Exp
litE (Lit -> ExpQ) -> Lit -> ExpQ
forall a b. (a -> b) -> a -> b
$ Integer -> Lit
intPrimL (Integer -> Lit) -> Integer -> Lit
forall a b. (a -> b) -> a -> b
$ Int64 -> Integer
forall a. Integral a => a -> Integer
toInteger (Int64 -> Integer) -> Int64 -> Integer
forall a b. (a -> b) -> a -> b
$ ByteString -> Int64
BL.length ByteString
b
        ctE :: ExpQ
ctE = Lit -> ExpQ
forall (m :: * -> *). Quote m => Lit -> m Exp
litE (Lit -> ExpQ) -> Lit -> ExpQ
forall a b. (a -> b) -> a -> b
$ [Word8] -> Lit
stringPrimL ([Word8] -> Lit) -> [Word8] -> Lit
forall a b. (a -> b) -> a -> b
$ ByteString -> [Word8]
BL.unpack ByteString
b
#else
bytestringLazyE b =
    [| B8.pack $s |]
  where
    s = litE $ stringL $ BL8.unpack b
#endif
mkEntry :: EmbeddableEntry -> ExpQ
mkEntry :: EmbeddableEntry -> ExpQ
mkEntry (EmbeddableEntry Text
loc ByteString
mime (Left (Text
etag, ByteString
ct))) =
    [|
        Left $
            EmbeddedEntry
                (T.pack $ExpQ
locE)
                $(ByteString -> ExpQ
bytestringE ByteString
mime)
                $(ByteString -> ExpQ
bytestringE (ByteString -> ExpQ) -> ByteString -> ExpQ
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
T.encodeUtf8 Text
etag)
                (1 == I# $ExpQ
compressedE)
                $(ByteString -> ExpQ
bytestringLazyE ByteString
ct')
        |]
  where
    locE :: ExpQ
locE = Lit -> ExpQ
forall (m :: * -> *). Quote m => Lit -> m Exp
litE (Lit -> ExpQ) -> Lit -> ExpQ
forall a b. (a -> b) -> a -> b
$ String -> Lit
stringL (String -> Lit) -> String -> Lit
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
loc
    (Bool
compressed, ByteString
ct') = ByteString -> ByteString -> (Bool, ByteString)
tryCompress ByteString
mime ByteString
ct
    compressedE :: ExpQ
compressedE = Lit -> ExpQ
forall (m :: * -> *). Quote m => Lit -> m Exp
litE (Lit -> ExpQ) -> Lit -> ExpQ
forall a b. (a -> b) -> a -> b
$ Integer -> Lit
intPrimL (Integer -> Lit) -> Integer -> Lit
forall a b. (a -> b) -> a -> b
$ if Bool
compressed then Integer
1 else Integer
0
mkEntry (EmbeddableEntry Text
loc ByteString
mime (Right ExpQ
expr)) =
    [|
        Right $
            ReloadEntry
                (T.pack $ExpQ
locE)
                $(ByteString -> ExpQ
bytestringE ByteString
mime)
                $ExpQ
expr
        |]
  where
    locE :: ExpQ
locE = Lit -> ExpQ
forall (m :: * -> *). Quote m => Lit -> m Exp
litE (Lit -> ExpQ) -> Lit -> ExpQ
forall a b. (a -> b) -> a -> b
$ String -> Lit
stringL (String -> Lit) -> String -> Lit
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
loc
embeddedToFile :: EmbeddedEntry -> File
embeddedToFile :: EmbeddedEntry -> File
embeddedToFile EmbeddedEntry
entry =
    File
        { fileGetSize :: Integer
fileGetSize = Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length (ByteString -> Int) -> ByteString -> Int
forall a b. (a -> b) -> a -> b
$ EmbeddedEntry -> ByteString
embContent EmbeddedEntry
entry
        , fileToResponse :: Status -> ResponseHeaders -> Response
fileToResponse = \Status
s ResponseHeaders
h ->
            let h' :: ResponseHeaders
h' =
                    if EmbeddedEntry -> Bool
embCompressed EmbeddedEntry
entry
                        then ResponseHeaders
h ResponseHeaders -> ResponseHeaders -> ResponseHeaders
forall a. [a] -> [a] -> [a]
++ [(HeaderName
"Content-Encoding", ByteString
"gzip")]
                        else ResponseHeaders
h
             in Status -> ResponseHeaders -> Builder -> Response
W.responseBuilder Status
s ResponseHeaders
h' (Builder -> Response) -> Builder -> Response
forall a b. (a -> b) -> a -> b
$ ByteString -> Builder
byteStringInsert (ByteString -> Builder) -> ByteString -> Builder
forall a b. (a -> b) -> a -> b
$ EmbeddedEntry -> ByteString
embContent EmbeddedEntry
entry
        , 
          
          
          
          
          
          fileName :: Piece
fileName = Text -> Piece
unsafeToPiece (Text -> Piece) -> Text -> Piece
forall a b. (a -> b) -> a -> b
$ EmbeddedEntry -> Text
embLocation EmbeddedEntry
entry
        , fileGetHash :: IO (Maybe ByteString)
fileGetHash =
            Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> IO (Maybe ByteString))
-> Maybe ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$
                if ByteString -> Bool
B.null (EmbeddedEntry -> ByteString
embEtag EmbeddedEntry
entry)
                    then Maybe ByteString
forall a. Maybe a
Nothing
                    else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ EmbeddedEntry -> ByteString
embEtag EmbeddedEntry
entry
        , fileGetModified :: Maybe EpochTime
fileGetModified = Maybe EpochTime
forall a. Maybe a
Nothing
        }
reloadToFile :: ReloadEntry -> IO File
reloadToFile :: ReloadEntry -> IO File
reloadToFile ReloadEntry
entry = do
    (Text
etag, ByteString
ct) <- ReloadEntry -> IO (Text, ByteString)
reloadContent ReloadEntry
entry
    let etag' :: ByteString
etag' = Text -> ByteString
T.encodeUtf8 Text
etag
    File -> IO File
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (File -> IO File) -> File -> IO File
forall a b. (a -> b) -> a -> b
$
        File
            { fileGetSize :: Integer
fileGetSize = Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Integer) -> Int64 -> Integer
forall a b. (a -> b) -> a -> b
$ ByteString -> Int64
BL.length ByteString
ct
            , fileToResponse :: Status -> ResponseHeaders -> Response
fileToResponse = \Status
s ResponseHeaders
h -> Status -> ResponseHeaders -> ByteString -> Response
W.responseLBS Status
s ResponseHeaders
h ByteString
ct
            , 
              fileName :: Piece
fileName = Text -> Piece
unsafeToPiece (Text -> Piece) -> Text -> Piece
forall a b. (a -> b) -> a -> b
$ ReloadEntry -> Text
reloadLocation ReloadEntry
entry
            , fileGetHash :: IO (Maybe ByteString)
fileGetHash = Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> IO (Maybe ByteString))
-> Maybe ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ if Text -> Bool
T.null Text
etag then Maybe ByteString
forall a. Maybe a
Nothing else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
etag'
            , fileGetModified :: Maybe EpochTime
fileGetModified = Maybe EpochTime
forall a. Maybe a
Nothing
            }
filemapToSettings :: M.HashMap T.Text (MimeType, IO File) -> StaticSettings
filemapToSettings :: HashMap Text (ByteString, IO File) -> StaticSettings
filemapToSettings HashMap Text (ByteString, IO File)
mfiles =
    (String -> StaticSettings
defaultWebAppSettings String
"")
        { ssLookupFile = lookupFile
        , ssGetMimeType = lookupMime
        }
  where
    piecesToFile :: [Piece] -> Text
piecesToFile [Piece]
p = Text -> [Text] -> Text
T.intercalate Text
"/" ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Piece -> Text) -> [Piece] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Piece -> Text
fromPiece [Piece]
p
    lookupFile :: [Piece] -> IO LookupResult
lookupFile [] = LookupResult -> IO LookupResult
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LookupResult
LRNotFound
    lookupFile [Piece]
p =
        case Text
-> HashMap Text (ByteString, IO File)
-> Maybe (ByteString, IO File)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
M.lookup ([Piece] -> Text
piecesToFile [Piece]
p) HashMap Text (ByteString, IO File)
mfiles of
            Maybe (ByteString, IO File)
Nothing -> LookupResult -> IO LookupResult
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LookupResult
LRNotFound
            Just (ByteString
_, IO File
act) -> File -> LookupResult
LRFile (File -> LookupResult) -> IO File -> IO LookupResult
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO File
act
    lookupMime :: File -> m ByteString
lookupMime (File{fileName :: File -> Piece
fileName = Piece
p}) =
        case Text
-> HashMap Text (ByteString, IO File)
-> Maybe (ByteString, IO File)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
M.lookup (Piece -> Text
fromPiece Piece
p) HashMap Text (ByteString, IO File)
mfiles of
            Just (ByteString
mime, IO File
_) -> ByteString -> m ByteString
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
mime
            Maybe (ByteString, IO File)
Nothing -> ByteString -> m ByteString
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> m ByteString) -> ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
defaultMimeLookup (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Piece -> Text
fromPiece Piece
p
entriesToSt :: [Either EmbeddedEntry ReloadEntry] -> StaticSettings
entriesToSt :: [Either EmbeddedEntry ReloadEntry] -> StaticSettings
entriesToSt [Either EmbeddedEntry ReloadEntry]
entries = HashMap Text (ByteString, IO File)
hmap HashMap Text (ByteString, IO File)
-> StaticSettings -> StaticSettings
forall a b. a -> b -> b
`seq` HashMap Text (ByteString, IO File) -> StaticSettings
filemapToSettings HashMap Text (ByteString, IO File)
hmap
  where
    embFiles :: [(Text, (ByteString, IO File))]
embFiles =
        [(EmbeddedEntry -> Text
embLocation EmbeddedEntry
e, (EmbeddedEntry -> ByteString
embMime EmbeddedEntry
e, File -> IO File
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (File -> IO File) -> File -> IO File
forall a b. (a -> b) -> a -> b
$ EmbeddedEntry -> File
embeddedToFile EmbeddedEntry
e)) | EmbeddedEntry
e <- [Either EmbeddedEntry ReloadEntry] -> [EmbeddedEntry]
forall a b. [Either a b] -> [a]
lefts [Either EmbeddedEntry ReloadEntry]
entries]
    reloadFiles :: [(Text, (ByteString, IO File))]
reloadFiles = [(ReloadEntry -> Text
reloadLocation ReloadEntry
r, (ReloadEntry -> ByteString
reloadMime ReloadEntry
r, ReloadEntry -> IO File
reloadToFile ReloadEntry
r)) | ReloadEntry
r <- [Either EmbeddedEntry ReloadEntry] -> [ReloadEntry]
forall a b. [Either a b] -> [b]
rights [Either EmbeddedEntry ReloadEntry]
entries]
    hmap :: HashMap Text (ByteString, IO File)
hmap = [(Text, (ByteString, IO File))]
-> HashMap Text (ByteString, IO File)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
M.fromList ([(Text, (ByteString, IO File))]
 -> HashMap Text (ByteString, IO File))
-> [(Text, (ByteString, IO File))]
-> HashMap Text (ByteString, IO File)
forall a b. (a -> b) -> a -> b
$ [(Text, (ByteString, IO File))]
embFiles [(Text, (ByteString, IO File))]
-> [(Text, (ByteString, IO File))]
-> [(Text, (ByteString, IO File))]
forall a. [a] -> [a] -> [a]
++ [(Text, (ByteString, IO File))]
reloadFiles
mkSettings :: IO [EmbeddableEntry] -> ExpQ
mkSettings :: IO [EmbeddableEntry] -> ExpQ
mkSettings IO [EmbeddableEntry]
action = do
    [EmbeddableEntry]
entries <- IO [EmbeddableEntry] -> Q [EmbeddableEntry]
forall a. IO a -> Q a
runIO IO [EmbeddableEntry]
action
    [|entriesToSt $([ExpQ] -> ExpQ
forall (m :: * -> *). Quote m => [m Exp] -> m Exp
listE ([ExpQ] -> ExpQ) -> [ExpQ] -> ExpQ
forall a b. (a -> b) -> a -> b
$ (EmbeddableEntry -> ExpQ) -> [EmbeddableEntry] -> [ExpQ]
forall a b. (a -> b) -> [a] -> [b]
map EmbeddableEntry -> ExpQ
mkEntry [EmbeddableEntry]
entries)|]
shouldCompress :: MimeType -> Bool
shouldCompress :: ByteString -> Bool
shouldCompress ByteString
m = ByteString
"text/" ByteString -> ByteString -> Bool
`B.isPrefixOf` ByteString
m Bool -> Bool -> Bool
|| ByteString
m ByteString -> [ByteString] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ByteString]
extra
  where
    extra :: [ByteString]
extra =
        [ ByteString
"application/json"
        , ByteString
"application/javascript"
        , ByteString
"application/ecmascript"
        ]
tryCompress :: MimeType -> BL.ByteString -> (Bool, BL.ByteString)
tryCompress :: ByteString -> ByteString -> (Bool, ByteString)
tryCompress ByteString
mime ByteString
ct
    | ByteString -> Bool
shouldCompress ByteString
mime = (Bool
c, ByteString
ct')
    | Bool
otherwise = (Bool
False, ByteString
ct)
  where
    compressed :: ByteString
compressed = ByteString -> ByteString
compress ByteString
ct
    c :: Bool
c = ByteString -> Int64
BL.length ByteString
compressed Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< ByteString -> Int64
BL.length ByteString
ct
    ct' :: ByteString
ct' = if Bool
c then ByteString
compressed else ByteString
ct