Why is main executable busy when calling external executable with Shelly.Background - multithreading

I am trying to write a program with Shelly to compile Delphi projects in parallel. I thought the program would be blocked while waiting for the Delphi compilers to return. But my program starts to max out one CPU-core after compiled 2 projects. I couldn't work out what it's so busy doing. Please help? Thanks.
ps: I am quite new to Haskell, if I'm not implementing this the right way, pointers are appreciated.
{-# LANGUAGE OverloadedStrings, ExtendedDefaultRules #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
import Shelly
import Shelly.Background
import Control.Monad
import Control.Arrow
import System.IO.Temp (withSystemTempDirectory)
import System.Directory (getCurrentDirectory)
import System.FilePath (splitFileName)
import Data.Text.Lazy (Text, pack)
default (Int, Text)
dcc32 = command "dcc32" ["-RC:\\Program Files\\Borland\\BDS\\4.0\\Lib", "-Q", "-H", "-W", "-B"]
compile project = liftIO $ withSystemTempDirectory "TempDCU_" compile'
where
compile' tmpDir = shellyNoDir $ silently $
chdir dir (dcc32 [toTextIgnore file, pack $ "-N" ++ tmpDir])
(dir, file) = mapTuple (fromText . pack) $ splitFileName project
mapTuple = join (***)
compilePooled n projects = shellyNoDir $ jobs n (\job -> mapM (background job . compile) projects)
projectList = [
"C:\\Path\\to\\project1.dpr",
"C:\\Path\\to\\project2.dpr",
"C:\\Path\\to\\project3.dpr",
"C:\\Path\\to\\project4.dpr",
]
main = do
output <- compilePooled 2 projectList
shellyNoDir $ mapM getBgResult output >>= mapM_ inspect

Related

how to list the functions exported by a Haskell module from an .hs script?

I am aware of this thread and the agreed-upon ghci :browse command, but I am looking for something similar to run from a script.hs file:
Say I have a module that I can import into my script.hs. How do I then view the list of functions I have just gained access to?
What I've settled on for now
Adapting this thread that suggests the now-deprecated ghc-mod command-line program, I am
calling the terminal command ghc -e ':browse <module, e.g. Data.List>'
from my script.hs using Shelly.
My full script:
#!/usr/bin/env runghc
{-# LANGUAGE OverloadedStrings #-}
import Safe (headDef)
import Shelly
import System.Environment (getArgs)
import qualified Data.Text as T
mdl :: IO String
mdl = getArgs >>= return . headDef "Data.List"
runShelly :: String -> IO ()
runShelly mdl = shelly $ silently $ do
out <- run "ghc" ["-e", T.pack (":browse " ++ mdl)]
let lns = T.lines out
liftIO $ mapM_ (putStrLn .T.unpack) $ lns
main :: IO ()
main = mdl >>= runShelly
This way I can pass the module name on the command line as <script> <module> and get back the functions, one per line. It defaults to Data.List if I pass no arguments.
So that's a solution, but surely there must be handier introspection facilities than this?

Haskell Twitch Library not working as expected

I am playing around with the Twitch library:
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Twitch
import Data.Default
import Turtle.Prelude
import RIO
main :: IO ()
main = do
print "hi"
let p = "C:\\Users\\unicorn\\programming\\listenerDir"
print "before"
liftIO $ runWithConfig p ((\c -> c {dirs=[p]}) def) $ do -- marked
"*.csv" |> \f -> print f -- marked
print "here"
return ()
when i compile and run the above program without the liftIO ... (so leaving out the marked lines) call it runs fine and prints the messages. (but then obviously, the file listener is not registered and running, so it is not the desired outcome.)
However, when compiled and run as is, it doesn't do anything, not even printing hi and before. any idea why that is the case here?
I have tried to follow the examples of the library but I can't figure out why it just hangs.
UPDATE:
apparently it has something to do with the dirs replacement I am doing for the def configuration
UPDATE:
I have also tried it the following way:
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Twitch
import Data.Default
import Turtle.Prelude
import RIO
import System.IO.Unsafe
import System.FilePath.Windows
main :: IO ()
main = do
let p = "C:\\" </> "Users" </> "unicorn" </> "programming" </> "simpleUID" </> "lib_app_setup" </> "kofax-valet" </> "testingDir"
ops = Options LogToStdout Nothing (Just p) False DebounceDefault 0 300 False
print "starting"
print p
defaultMainWithOptions ops $ do
"*.csv" > \f -> print f
with the same result
looking it up in the source, defaultMainWithOptions should also print stuff to stdout; but that doesn't happen either...
fyi: I asked this question on reddit but didn't get an answer there, so I suspected a bigger problem that might not be just my unfamiliarity with the library and therefore posted it here
Update:
this is the full output of cabal run for the second code:
unicorn#LAPTOP ~/programming/haskell/listenerTest
$ cabal run
Build profile: -w ghc-8.10.1 -O1
In order, the following will be built (use -v for more details):
- listenerTest-0.1.0.0 (exe:listenerTest) (file Main.hs changed)
Preprocessing executable 'listenerTest' for listenerTest-0.1.0.0..
Building executable 'listenerTest' for listenerTest-0.1.0.0..
[1 of 1] Compiling Main
( Main.hs, C:\Users\unicorn\programming\haskell\listenerTest\dist-newstyle
\build\x86_64-windows\ghc-8.10.1\listenerTest-0.1.0.0\x\listenerTest\build
\listenerTest\listenerTest-tmp\Main.o )
Linking C:\Users\unicorn\programming\haskell\listenerTest\dist-newstyle\build
\x86_64-windows\ghc-8.10.1\listenerTest-0.1.0.0\x\listenerTest\build
\listenerTest\listenerTest.exe ...
unicorn#LAPTOP ~/programming/haskell/listenerTest
$
afterwards i had to Ctrl+c and then also kill the task

Error with function resolution while dynamically loading a .o object from Haskell

I am writing a tool for which I want a modular architecture. By that I mean that the users would be able to write down a list of the modules they want to be loaded at start-up and my tool would be loading the corresponding .o for me.
Here is the code I managed to write up until now:
module Core where
import Data.Monoid ((<>))
import Data.Text (pack, unpack)
import System.Directory (getHomeDirectory)
import System.Plugins.DynamicLoader
loadPlugins :: [Text] -> IO ()
loadPlugins plugins = do
home <- getHomeDirectory
-- addDLL "/home/tchoutri/.stack/programs/x86_64-linux/ghc-tinfo6-8.4.3/lib/ghc-8.4.3/base-4.11.1.0/libHSbase-4.11.1.0-ghc8.4.3.so"
let paths = fmap (\x -> (pack home) <> "/.local/lib/polynot/polynot-" <> x <> ".o") plugins
forM_ paths $ \path -> load path
where
load path = do
m <- loadModuleFromPath (unpack path) (Just $ unpack path)
resolveFunctions
loadFunction m "runPlugin"
The plugin I'm trying to load at this moment is very simple:
{-# LANGUAGE OverloadedStrings #-}
module Polynot.Plugin.Twitter where
runPlugin :: IO ()
runPlugin = putStrLn "[Twitter] 'sup"
It is compiled with stack ghc -- --make -dynamic -fPIC -O3 twitter.hs. It is then renamed polynot-twitter.o, in ~/.local/lib/polynot/.
The compilation goes well, and when I run stack exec -- polynot, I get this error:
polynot: user error (Unable to get qualified name from: /home/tchoutri/.local/lib/polynot/polynot-twitter.o)
A quick google search showed me that the only instances of this error appear in the source code. :/
Moreover, I use the git version of dynamic-loader.
(I may be mistaken about my choice for a modular architecture, I totally accept that. If you have a better approach I could use, you can totally comment on it :)
I wasn't able to duplicate your error. I get a Prelude.head: empty list exception instead.
However, my guess is that it has to do with the functions in dynamic-loader expecting to load modules from a hierarchical directory structure that matches the module hierarchy.
In a nutshell, if I store the plugin in:
~/.local/lib/polynot/Polynot/Plugin/Twitter.o
and use loadModule like so:
loadModule "Polynot.Plugin.Twitter"
(Just "/home/buhr/.local/lib/polynot") (Just "o")
then it works okay for me.
The Main.hs I used was the following:
{-# LANGUAGE OverloadedStrings #-}
import Control.Monad (forM_)
import Data.Monoid ((<>))
import Data.Text (pack, unpack, Text)
import System.Directory (getHomeDirectory)
import System.Plugins.DynamicLoader
loadPlugins :: [Text] -> IO ()
loadPlugins plugins = do
home <- getHomeDirectory
let basedir = (pack home) <> "/.local/lib/polynot"
forM_ plugins (load basedir)
where
load dir plugin = do
m <- loadModule (unpack plugin) (Just $ unpack dir) (Just "o")
resolveFunctions
entry <- loadFunction m "runPlugin"
entry
main = do
putStrLn "starting!"
loadPlugins ["Polynot.Plugin.Twitter"]
putStrLn "done!"

Haskell Shelly sample code

I'm trying to figure out how to use the Shelly (Shell.Pipe) library.
So far i've got:
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
import Control.Applicative
import Data.List(sort)
import Shelly.Pipe
import Data.Text.Lazy as LT
default (LT.Text)
findExt ext = findWhen (pure . hasExt ext)
main = shelly $ verbosely $ do
cd bookPath
findExt "epub" "."
I can find all the epub files but then I have no idea how to operate on each of the epub file ?
For example I want to run ebook-convert command on those file names wrapped by Sh Monad.
Btw: The examples are really scarce on the internet...
And it is very confusing that there are two similar libries:Shelly and Shelly.Pipe. The functions inside these two share same name with different Types:
In Shelly.Pipe:
find :: FilePath -> Sh FilePath
find = sh1s S.find
In Shelly:
find :: FilePath -> ShIO [FilePath]
Really frustrating !
PS: With the help from John Wiegley
I finally got the code working.
I post the code below for people who might use it.
Pay attention to the use of unpack.
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
import Control.Applicative
import Data.List(sort)
import Control.Monad
import Shelly
import System.Directory
import Data.Text
import System.FilePath
default (Text)
bookPath = "/dir/to/books"
main = shelly $ verbosely $ do
fnames <- Shelly.find bookPath --fnames can not be processed by normal pure String processing functions and need to be "escaped"
forM_ fnames $ \n-> liftIO $ putStrLn $ ProcessBookFileName $ unpack $ toTextIgnore n --ProcessBookFileName::String->String
From what I can gather, you don't want to use the Shelly.Pipe module, just the Shelly module. The ShIO monad implements MonadIO, which allows you to execute arbitrary IO actions while inside ShIO. This would let you do something like
convertEpub :: FilePath -> IO ()
convertEpub fname = undefined
main = shelly $ do
cd "projects/haskell/testing"
liftIO $ putStrLn "Hello, world! I'm in Shelly"
fnames <- find (pure . hasExt "hs") "."
liftIO $ forM_ fnames $ \fname -> do
putStrLn $ "Processing file " ++ show fname
convertEpub fname

How to take lazy bytestring from zip archive without heap overflow

I want to take first five bytes from the fist file in zip archive. I use zip-archive package for decompression:
import qualified Data.ByteString.Lazy as L
import Data.Maybe
import System.Environment (getArgs)
import Codec.Archive.Zip
main = do
f:_ <- getArgs
print . L.take 5 . fromEntry . head . zEntries . toArchive =<< L.readFile f
This code works for small archives but I got heap overflow with big ones. For example:
./zip-arch test.zip +RTS -p -hy -M100M
for this archive gives this heap profile
Consider calling out to unzip. It's not super haskelly but it does the job. Perhaps all the haters out there should spend more time fixing or replacing broken libraries like zip-archive and less time on stackoverflow.
Standard disclaimer: no error checking present. this may leak handles. lazy i/o is lazy.
import System.Environment (getArgs)
import System.IO (hSetBinaryMode)
import System.Process (StdStream(...), createProcess, proc, close_fds, std_out)
import qualified Data.ByteString.Lazy as L
unzipLBS :: FilePath -> IO L.ByteString
unzipLBS file = do
let args = proc "unzip" ["-p", file]
args' = args { std_out = CreatePipe, close_fds = True }
(_, Just hOut, _, _) <- createProcess args'
hSetBinaryMode hOut True
L.hGetContents hOut
main :: IO ()
main = do
f:_ <- getArgs
print . L.take 5 =<< unzipLBS f
Seems to work:
$ runghc -Wall unzip.hs ~/Downloads/test.zip
Chunk ",+\227F\149" Empty
I've read the explanation of the zip-archive author and decided to make recommended repairs. I've finished with a new library - zip-conduit. Its main feature is constant memory usage without lazy IO. To take first five bytes from the fist file in the zip archive you can write:
import System.Environment
import Data.Conduit
import qualified Data.Conduit.Binary as CB
import Codec.Archive.Zip
main = do
f:_ <- getArgs
res <- withArchive f $ do
name:_ <- fileNames
source <- getSource name
runResourceT $ source $$ CB.take 5
print res

Resources