Implement creating ZIP (JAR) files from tree of classes.
[hs-java.git] / Java / JAR / Archive.hs
index 035f1e1d5b4ec31085e0b1d6a9676bb0d64dddcf..5425ab5aa7b7d72e1a298c111240fe566cda6794 100644 (file)
@@ -1,32 +1,55 @@
-
+-- | This module defines functions to read Java JAR files.
 module Java.JAR.Archive where
 
 import Control.Monad.Trans
-import qualified Control.Monad.State as St
 import qualified Codec.Archive.LibZip as Zip
 import Data.Binary
+import Data.List
 import qualified Data.ByteString.Lazy as B
+import System.FilePath
 
 import Java.ClassPath.Types
 import Java.ClassPath.Common
 import JVM.ClassFile
 import JVM.Converter
 
-readJAR :: FilePath -> IO [Tree CPEntry]
-readJAR jarfile = do
-  files <- Zip.withArchive [] jarfile $ Zip.fileNames []
-  return $ mapF (NotLoadedJAR jarfile) (buildTree files)
+readJAREntry :: (Enum a) => FilePath -> String -> IO (Maybe [a])
+readJAREntry jarfile path = do
+  Zip.catchZipError (Just `fmap` (Zip.withArchive [] jarfile $ Zip.fileContents [] path))
+                    (\_ -> return Nothing)
+
+-- | Read all entires from JAR file
+readAllJAR :: FilePath -> IO [Tree CPEntry]
+readAllJAR jarfile = do
+    files <- Zip.withArchive [] jarfile $ Zip.fileNames []
+    return $ mapF (NotLoadedJAR jarfile) (buildTree $ filter good files)
+  where
+    good file = ".class" `isSuffixOf` file
 
+-- | Read one class from JAR file
 readFromJAR :: FilePath -> FilePath -> IO (Class Direct)
 readFromJAR jarfile path = do
   content <- Zip.withArchive [] jarfile $ Zip.fileContents [] path
   let bstr = B.pack content
   return $ classFile2Direct (decode bstr)
 
-addJAR :: FilePath -> ClassPath ()
-addJAR jarfile = do
-  classes <- liftIO $ readJAR jarfile
-  cp <- St.get
-  let cp' = merge $ cp ++ classes
-  St.put cp'
+checkClassTree :: [Tree CPEntry] -> IO [Tree (FilePath, Class Direct)]
+checkClassTree forest = mapFMF check forest
+  where
+    check _ (NotLoaded path) = do
+       cls <- parseClassFile path
+       return (path, cls)
+    check a (Loaded path cls) = return (a </> path, cls)
+    check a (NotLoadedJAR jar path) = do
+       cls <- readFromJAR jar (a </> path)
+       return (a </> path, cls)
+    check a (LoadedJAR _ cls) =
+       return (a </> show (thisClass cls), cls)
+
+zipJAR :: [Tree (FilePath, Class Direct)] -> Zip.Archive ()
+zipJAR forest = do
+    mapFM go forest
+    return ()
+  where
+    go (path, cls) = Zip.addFile path =<< Zip.sourceBuffer (B.unpack $ encodeClass cls)