[Haskell-beginners] "system" call uses a different shell, or does not pick up the whole environment

Matthew wonderzombie at gmail.com
Tue Aug 28 17:40:09 CEST 2012


Not to further discourage you from experimenting, but xargs can also
run commands in parallel. Check out the -P argument. :)

On Tue, Aug 28, 2012 at 8:19 AM, Hong Yang <hyangfji at gmail.com> wrote:
> Hi Brent,
>
> Thanks for the xargs command info. I did not know it before.
>
> The other reason I want to play with my mapm version is eventually I want to
> make it concurrent.
>
> Thanks again,
>
> Hong
>
>
> On Tue, Aug 28, 2012 at 10:08 AM, Brent Yorgey <byorgey at seas.upenn.edu>
> wrote:
>>
>> I do not know the solution to your problem -- dealing with shells,
>> environments, etc. can be tricky.
>>
>> However, do you know about the 'xargs' command?  E.g. your example
>> could be accomplished with
>>
>>   ls | xargs -L 1 -I{} cp -pr {} destination_dir/{}
>>
>> -Brent
>>
>> On Tue, Aug 28, 2012 at 09:58:16AM -0500, Hong Yang wrote:
>> > Hi,
>> >
>> > I am trying to mimic mapM() at shell command line. I define the
>> > interface
>> > as "mapm cmd2 cmd1," so cmd2 will be run for each of the cmd1 results.
>> > "$_"
>> > can be used inside cmd2 to represent the current cmd1 result.
>> >
>> > For example, the command
>> >         mapm    'cp -pr $_ destination_dir/$_'    ls
>> > copies everything under the current directory to the destination
>> > directory.
>> >
>> > The code is as follows:
>> >
>> > --
>> > module Main where
>> >
>> > import System.Environment ( getArgs )
>> > import System.Exit
>> > import System.IO
>> > import System.Process
>> > import Text.Regex
>> > import Text.Regex.Posix
>> >
>> > main = do
>> >     hs_argv <- getArgs
>> >     if length hs_argv /= 2
>> >       then
>> >         putStrLn "wrong arguments!" >> exitFailure
>> >       else do
>> >         let [cmd2, cmd1] = hs_argv
>> >         (_, hOut, hErr, _) <- runInteractiveCommand cmd1
>> >         err <- hGetContents hErr
>> >         hClose hErr
>> >         if null err
>> >           then do
>> >             out <- hGetContents hOut
>> >             mapM (f cmd2) (lines out)
>> >           else
>> >             putStr err >> exitFailure
>> >
>> > f :: String -> String -> IO ExitCode
>> > f cmd2 item = system cmd2'
>> >   where cmd2' = if cmd2 =~ "\\$\\_"::Bool
>> >                 then subRegex (mkRegex "\\$\\_") cmd2 item
>> >                 else cmd2
>> > --
>> >
>> > It works, except one issue that is bothering me.
>> >
>> > If I issue
>> >         mapm    'lt $_'    ls,
>> > I get a bunch of
>> >         /bin/sh: lt: command not found,
>> > while I expect it act the same as
>> >         mapm    'ls -Alrt --color=auto $_'    ls,
>> > because "lt" is aliased to "ls -Alrt --color=auto."
>> >
>> > Notice "/bin/sh" above. My shell is actually tcsh. All the aliases are
>> > in
>> > ~/.cshrc.
>> >
>> > I tried replacing "system cmd2'" with
>> >         system ("source ~/.cshrc; " ++ cmd2')
>> >     and
>> >         system ("tcsh -c " ++ "'source ~/.cshrc; " ++ cmd2' ++ "'"),
>> > but they did not solve the problem.
>> >
>> > Can someone please help me?
>> >
>> > Thanks,
>> >
>> > Hong
>>
>> > _______________________________________________
>> > Beginners mailing list
>> > Beginners at haskell.org
>> > http://www.haskell.org/mailman/listinfo/beginners
>>
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



More information about the Beginners mailing list