MediaBag: improve detection of absolute paths.
Previously we used System.FilePath's isRelative to determine when paths are relative (since absolute paths need to get a new name based on the sha1 hash). But this has an OS-specific behavior and actually returns True on Windows for paths like `/media/file.png`. This ought to fix #7881.
This commit is contained in:
parent
40b174c770
commit
d40236805d
2 changed files with 6 additions and 2 deletions
|
@ -53,6 +53,7 @@ import Network.URI (unEscapeString)
|
|||
import System.Directory (createDirectoryIfMissing)
|
||||
import System.Environment (getEnv)
|
||||
import System.FilePath ((</>), takeDirectory, normalise)
|
||||
import qualified System.FilePath.Posix as Posix
|
||||
import System.IO (stderr)
|
||||
import System.IO.Error
|
||||
import System.Random (StdGen)
|
||||
|
@ -234,6 +235,6 @@ adjustImagePath dir mediabag (Image attr lab (src, tit)) =
|
|||
case lookupMedia (T.unpack src) mediabag of
|
||||
Nothing -> Image attr lab (src, tit)
|
||||
Just item ->
|
||||
let fullpath = dir <> "/" <> mediaPath item
|
||||
let fullpath = dir Posix.</> mediaPath item
|
||||
in Image attr lab (T.pack fullpath, tit)
|
||||
adjustImagePath _ _ x = x
|
||||
|
|
|
@ -29,6 +29,8 @@ import qualified Data.Map as M
|
|||
import Data.Maybe (fromMaybe, isNothing)
|
||||
import Data.Typeable (Typeable)
|
||||
import System.FilePath
|
||||
import qualified System.FilePath.Posix as Posix
|
||||
import qualified System.FilePath.Windows as Windows
|
||||
import Text.Pandoc.MIME (MimeType, getMimeTypeDef, extensionFromMimeType)
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
|
@ -78,7 +80,8 @@ insertMedia fp mbMime contents (MediaBag mediamap) =
|
|||
, mediaMimeType = mt }
|
||||
fp' = canonicalize fp
|
||||
uri = parseURI fp
|
||||
newpath = if isRelative fp
|
||||
newpath = if Posix.isRelative fp
|
||||
&& Windows.isRelative fp
|
||||
&& isNothing uri
|
||||
&& ".." `notElem` splitDirectories fp
|
||||
then T.unpack fp'
|
||||
|
|
Loading…
Add table
Reference in a new issue