Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  associative arrays (Adrien Haxaire)
   2. Re:  Are tuples really needed? (David McBride)
   3.  "system" call uses a different shell,    or does not pick up
      the whole environment (Hong Yang)
   4. Re:  "system" call uses a different shell, or does not pick
      up the whole environment (Brent Yorgey)
   5. Re:  "system" call uses a different shell, or does not pick
      up the whole environment (Hong Yang)
   6. Re:  "system" call uses a different shell, or does not pick
      up the whole environment (Michael Orlitzky)


----------------------------------------------------------------------

Message: 1
Date: Tue, 28 Aug 2012 14:29:16 +0200
From: Adrien Haxaire <adr...@haxaire.org>
Subject: Re: [Haskell-beginners] associative arrays
To: <beginners@haskell.org>
Message-ID: <b1d249b8bef91dcc2b878b0e8e041...@haxaire.org>
Content-Type: text/plain; charset=UTF-8; format=flowed

 On Sat, 25 Aug 2012 09:11:30 -0600, Nick Vanderweit wrote:
> I'd still recommend Data.Map, since it's a much more efficient data
> structure
> for the task.

 They are implemented as a tree, which is fine as long as you do not 
 want/need duplicates in your association list.

 They are also well documented and the extensive API will do most of 
 what you'll need. I use them a lot.


-- 
 Adrien Haxaire
 www.adrienhaxaire.org | @adrienhaxaire



------------------------------

Message: 2
Date: Tue, 28 Aug 2012 10:23:50 -0400
From: David McBride <toa...@gmail.com>
Subject: Re: [Haskell-beginners] Are tuples really needed?
To: "Carlos J. G. Duarte" <carlos.j.g.dua...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <CAN+Tr40Bf=UOv-cP00K-1UWxy=zh9Me=qwk-hzgcs1vlkmy...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Pattern matching makes tuples really useful.  Sometimes you just want to
return a pair of values and you don't feel like making a one off
constructor for it.

Eg: random :: (RandomGen g, Random a) => g -> (a, g).  Without tuples you'd
have to have a one off type data RandomGenWithRandom g a  = RGWR g a, which
is overkill, when you just wanted two values.

On Mon, Aug 27, 2012 at 9:47 PM, Carlos J. G. Duarte <
carlos.j.g.dua...@gmail.com> wrote:

> Sorry if this question is too insane, but I was wondering if tuples are
> really needed in Haskell. I mean, could tuples be generally replaced by
> variables unroll (f x y z) and explicit data types, or are there some
> things only possible to do via tuples?
>
> Thx in advance (and sorry if this looks silly).
>
>
> ______________________________**_________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/**mailman/listinfo/beginners<http://www.haskell.org/mailman/listinfo/beginners>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120828/1ad23bed/attachment-0001.htm>

------------------------------

Message: 3
Date: Tue, 28 Aug 2012 09:58:16 -0500
From: Hong Yang <hyang...@gmail.com>
Subject: [Haskell-beginners] "system" call uses a different shell,      or
        does not pick up the whole environment
To: beginners@haskell.org
Message-ID:
        <CA+_A4U5du4CTW=d+gq-hb4b7hz-vbmxlxsidukobobpbofl...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120828/54801be1/attachment-0001.htm>

------------------------------

Message: 4
Date: Tue, 28 Aug 2012 11:08:04 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] "system" call uses a different shell,
        or does not pick up the whole environment
To: beginners@haskell.org
Message-ID: <20120828150804.ga31...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

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@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners




------------------------------

Message: 5
Date: Tue, 28 Aug 2012 10:19:58 -0500
From: Hong Yang <hyang...@gmail.com>
Subject: Re: [Haskell-beginners] "system" call uses a different shell,
        or does not pick up the whole environment
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID:
        <CA+_A4U7L8zug5=ofnaz_qspcsukorjdhkaevoxztiwrd6mv...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

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 <byor...@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@haskell.org
> > http://www.haskell.org/mailman/listinfo/beginners
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120828/1ba3820e/attachment-0001.htm>

------------------------------

Message: 6
Date: Tue, 28 Aug 2012 11:35:50 -0400
From: Michael Orlitzky <mich...@orlitzky.com>
Subject: Re: [Haskell-beginners] "system" call uses a different shell,
        or does not pick up the whole environment
To: beginners@haskell.org
Message-ID: <503ce556.3010...@orlitzky.com>
Content-Type: text/plain; charset=UTF-8

On 08/28/12 11:19, Hong Yang 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.
> 

GNU Parallel is essentially xargs, run in parallel:

  http://www.gnu.org/software/parallel/

Might solve your problem albeit not in Haskell.



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 50, Issue 33
*****************************************

Reply via email to