aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--appveyor.yml63
-rw-r--r--src/Text/Pandoc/MediaBag.hs9
-rw-r--r--src/Text/Pandoc/Shared.hs9
-rw-r--r--tests/Tests/Shared.hs2
4 files changed, 52 insertions, 31 deletions
diff --git a/appveyor.yml b/appveyor.yml
index e117fb984..48957fc80 100644
--- a/appveyor.yml
+++ b/appveyor.yml
@@ -1,27 +1,46 @@
-branches:
- only:
- - master
+install:
+- cmd: 'git submodule update --init'
+- ps: |
+ choco install haskellplatform -version 2014.2.0.0 -y
+ # Haskell Platfrom package doesn't update PATH for the current shell instance
-cache:
-- "c:\\sr" # stack root, short paths == fewer problems
-- "%LOCALAPPDATA%\\Programs\\stack"
+ $env:Path += ";${env:ProgramFiles}\Haskell Platform\2014.2.0.0\bin"
+ $env:Path += ";${env:ProgramFiles}\Haskell Platform\2014.2.0.0\lib\extralibs\bin"
+ $env:Path += ";${env:ProgramFiles}\Haskell Platform\2014.2.0.0\mingw\bin"
+ choco install wixtoolset
+ cabal sandbox init
+ $env:Path += ";.\.cabal-sandbox\bin"
+ cabal update
+ cabal install --force hsb2hs
-build: off
+build_script:
+- ps: |
+ echo "PATH is $env:Path"
+ cabal install --force --enable-tests -fembed_data_files . pandoc-citeproc
-before_test:
-- ps: Invoke-WebRequest "https://github.com/commercialhaskell/stack/releases/download/v0.1.5.0/stack-0.1.5.0-x86_64-windows.zip" -OutFile stack.zip
-- ps: Invoke-WebRequest "https://github.com/fpco/minghc/blob/master/bin/7z.exe?raw=true" -OutFile 7z.exe
-- ps: Invoke-WebRequest "https://github.com/fpco/minghc/blob/master/bin/7z.dll?raw=true" -OutFile 7z.dll
-- 7z x -oc:\\stack stack.zip
-- move c:\\stack\\stack.exe stack.exe
-
-clone_folder: "c:\\pandoc"
-environment:
- global:
- STACK_ROOT: "c:\\sr"
+after_build:
+- ps: |
+ echo "PATH is $env:Path"
+ strip .\.cabal-sandbox\bin\pandoc.exe
+ strip .\.cabal-sandbox\bin\pandoc-citeproc.exe
+ .\.cabal-sandbox\bin\pandoc.exe -s --template data\templates\default.html -S README -o README.html
+ .\.cabal-sandbox\bin\pandoc.exe -s --template data\templates\default.rtf COPYING -t rtf -S -o COPYING.rtf
+ copy COPYRIGHT COPYRIGHT.txt
+ for /f "tokens=1-2 delims= " %%a in ('.\.cabal-sandbox\bin\pandoc --version') do (
+ @set VERSION=%%b
+ goto :next
+ )
+ :next
+ if "%VERSION%" == "" (
+ echo Error: could not determine version number.
+ exit /b 1
+ )
+ cd windows
+ echo Creating msi...
+ candle -dVERSION=%VERSION% pandoc.wxs
+ if %errorlevel% neq 0 exit /b %errorlevel%
+ light -sw1076 -ext WixUIExtension -ext WixUtilExtension -out pandoc-%VERSION%-windows.msi pandoc.wixobj
test_script:
-# The ugly echo "" hack is to avoid complaints about 0 being an invalid file
-# descriptor
-- echo "" | stack --arch i386 --no-terminal --install-ghc test
-
+- ps: |
+ cabal test
diff --git a/src/Text/Pandoc/MediaBag.hs b/src/Text/Pandoc/MediaBag.hs
index 1246cdc8f..e875d950e 100644
--- a/src/Text/Pandoc/MediaBag.hs
+++ b/src/Text/Pandoc/MediaBag.hs
@@ -37,6 +37,7 @@ module Text.Pandoc.MediaBag (
extractMediaBag
) where
import System.FilePath
+import qualified System.FilePath.Posix as Posix
import System.Directory (createDirectoryIfMissing)
import qualified Data.Map as M
import qualified Data.ByteString.Lazy as BL
@@ -67,7 +68,7 @@ insertMedia :: FilePath -- ^ relative path and canonical name of resource
-> MediaBag
-> MediaBag
insertMedia fp mbMime contents (MediaBag mediamap) =
- MediaBag (M.insert (splitPath fp) (mime, contents) mediamap)
+ MediaBag (M.insert (splitDirectories fp) (mime, contents) mediamap)
where mime = fromMaybe fallback mbMime
fallback = case takeExtension fp of
".gz" -> getMimeTypeDef $ dropExtension fp
@@ -77,14 +78,14 @@ insertMedia fp mbMime contents (MediaBag mediamap) =
lookupMedia :: FilePath
-> MediaBag
-> Maybe (MimeType, BL.ByteString)
-lookupMedia fp (MediaBag mediamap) = M.lookup (splitPath fp) mediamap
+lookupMedia fp (MediaBag mediamap) = M.lookup (splitDirectories fp) mediamap
-- | Get a list of the file paths stored in a 'MediaBag', with
-- their corresponding mime types and the lengths in bytes of the contents.
mediaDirectory :: MediaBag -> [(String, MimeType, Int)]
mediaDirectory (MediaBag mediamap) =
M.foldWithKey (\fp (mime,contents) ->
- (((joinPath fp), mime, fromIntegral $ BL.length contents):)) [] mediamap
+ (((Posix.joinPath fp), mime, fromIntegral $ BL.length contents):)) [] mediamap
-- | Extract contents of MediaBag to a given directory. Print informational
-- messages if 'verbose' is true.
@@ -95,7 +96,7 @@ extractMediaBag :: Bool
extractMediaBag verbose dir (MediaBag mediamap) = do
sequence_ $ M.foldWithKey
(\fp (_ ,contents) ->
- ((writeMedia verbose dir (joinPath fp, contents)):)) [] mediamap
+ ((writeMedia verbose dir (Posix.joinPath fp, contents)):)) [] mediamap
writeMedia :: Bool -> FilePath -> (FilePath, BL.ByteString) -> IO ()
writeMedia verbose dir (subpath, bs) = do
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index c44133e12..9bea0a65e 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -111,7 +111,8 @@ import Network.URI ( escapeURIString, isURI, nonStrictRelativeTo,
unEscapeString, parseURIReference, isAllowedInURI )
import qualified Data.Set as Set
import System.Directory
-import System.FilePath (joinPath, splitDirectories, pathSeparator, isPathSeparator)
+import System.FilePath (splitDirectories, isPathSeparator)
+import qualified System.FilePath.Posix as Posix
import Text.Pandoc.MIME (MimeType, getMimeType)
import System.FilePath ( (</>), takeExtension, dropExtension)
import Data.Generics (Typeable, Data)
@@ -832,7 +833,7 @@ readDefaultDataFile fname =
case lookup (makeCanonical fname) dataFiles of
Nothing -> err 97 $ "Could not find data file " ++ fname
Just contents -> return contents
- where makeCanonical = joinPath . transformPathParts . splitDirectories
+ where makeCanonical = Posix.joinPath . transformPathParts . splitDirectories
transformPathParts = reverse . foldl go []
go as "." = as
go (_:as) ".." = as
@@ -967,14 +968,14 @@ hush (Right x) = Just x
-- > collapseFilePath "parent/foo/.." == "parent"
-- > collapseFilePath "/parent/foo/../../bar" == "/bar"
collapseFilePath :: FilePath -> FilePath
-collapseFilePath = joinPath . reverse . foldl go [] . splitDirectories
+collapseFilePath = Posix.joinPath . reverse . foldl go [] . splitDirectories
where
go rs "." = rs
go r@(p:rs) ".." = case p of
".." -> ("..":r)
(checkPathSeperator -> Just True) -> ("..":r)
_ -> rs
- go _ (checkPathSeperator -> Just True) = [[pathSeparator]]
+ go _ (checkPathSeperator -> Just True) = [[Posix.pathSeparator]]
go rs x = x:rs
isSingleton [] = Nothing
isSingleton [x] = Just x
diff --git a/tests/Tests/Shared.hs b/tests/Tests/Shared.hs
index 9b55b7b1d..4d6076114 100644
--- a/tests/Tests/Shared.hs
+++ b/tests/Tests/Shared.hs
@@ -9,7 +9,7 @@ import Test.Framework.Providers.HUnit
import Test.HUnit ( assertBool, (@?=) )
import Text.Pandoc.Builder
import Data.Monoid
-import System.FilePath (joinPath)
+import System.FilePath.Posix (joinPath)
tests :: [Test]
tests = [ testGroup "normalize"