[Haskell-cafe] Re: wanted: haskell one-liners (in the perl sense of one-liners)

Thomas Hartman tphyahoo at gmail.com
Sun Mar 4 07:44:50 EST 2007


I think I could have most of the oneliner goodness of h4sh, without
having to do the module install, if I could figure out a way to
include modules with ghc -e.

or, alternatively some way to specify modules as a ghc flag, analogous to

perl -MPath::To::Module -e 'commands'

Can this be made to work?

(From http://haskell.org/haskellwiki/Simple_unix_tools, which seems to
be repeated somehow in h4sh, although I'm not completely certain on
that.)

***************************************

thartman at linodewhyou:~/learning/haskell/UnixTools$ echo "1234" | ghc
-e 'interact id'
1234
thartman at linodewhyou:~/learning/haskell/UnixTools$ echo "1234" | ghc
-e 'UnixTools.cat'

<interactive>:1:0:
   Bad interface file: UnixTools.hi
       UnixTools.hi: openBinaryFile: does not exist (No such file or directory)


thartman at linodewhyou:~/learning/haskell/UnixTools$ head -n23 UnixTools.hs
module UnixTools where
--
-- Some unix-like tools written in simple, clean Haskell
--
--

import Data.List
import Data.Char
import System.IO
import Text.Printf
.....
-- The 'cat' program
--
cat     = interact id

2007/3/4, Donald Bruce Stewart <dons at cse.unsw.edu.au>:
> Yes, it definitely is a little lagged. It should be ported to use lazy
> bytestrings too. I wsa more suggesting the one liners as examples of
> haskell use in the shell.
>
> tphyahoo:
> > That seems like a really great thing to have. But I had troubles installing
> > it.
> >
> > h4sh depends on hs-plugins.
> >
> > And...
> > ****************
> > thartman at linodewhyou:~/haskellInstalls/hs-plugins$ ./Setup.lhs configure
> > Setup.lhs: Warning: The field "hs-source-dir" is deprecated, please
> > use hs-source-dirs.
> > Configuring plugins-1.0...
> > configure: /usr/local/bin/ghc-pkg
> > configure: Dependency base-any: using base-2.0
> > configure: Dependency Cabal-any: using Cabal-1.1.6
> > Setup.lhs: cannot satisfy dependency haskell-src-any
> > thartman at linodewhyou:~/haskellInstalls/hs-plugins$
> > ****************
> > Advice?
> >
> > 2007/3/4, Donald Bruce Stewart <dons at cse.unsw.edu.au>:
> > >There's some nice one liners bundled with h4sh:
> > >
> > >    http://www.cse.unsw.edu.au/~dons/h4sh.html
> > >
> > >For example:
> > >
> > >    http://www.cse.unsw.edu.au/~dons/h4sh.txt
> > >
> > >If you recall, h4sh is a set of unix wrappers to the list library.
> > >I still use them everyday, though probably should put out a new release
> > >soon.
> > >
> > >-- Don
> > >
> > >
> > >tphyahoo:
> > >> To answer my original question, here's a few ways to accomplish what I
> > >> wanted with haskell
> > >>
> > >> Perl is still a lot faster than ghc -e, but I guess if you wanted
> > >> speed you could compile first.
> > >>
> > >> ********************************************************************
> > >>
> > >> thartman at linodewhyou:~/learning/haskell/UnixTools$ ls -l
> > >> total 16
> > >> -rw-r--r-- 1 thartman thartman 2726 Dec 20 07:56 UnixTools.hs
> > >> -rw-r--r-- 1 thartman thartman   82 Jan  7 07:18 echo.hs
> > >> -rwxr--r-- 1 thartman thartman  790 Mar  4 05:02 oneliners.sh
> > >> -rwxr--r-- 1 thartman thartman  646 Mar  4 04:18 oneliners.sh~
> > >>
> > >> thartman at linodewhyou:~/learning/haskell/UnixTools$ ./oneliners.sh
> > >> haskell, ghc -e pipe
> > >> 16
> > >>
> > >> real    0m1.652s
> > >> user    0m0.600s
> > >> sys     0m0.030s
> > >> **********
> > >> haskell, hmap pipe
> > >> 16
> > >>
> > >> real    0m1.549s
> > >> user    0m0.410s
> > >> sys     0m0.200s
> > >> **********
> > >> haskell, two pipes
> > >> 16
> > >>
> > >> real    0m2.153s
> > >> user    0m0.900s
> > >> sys     0m0.370s
> > >> **********
> > >> perl, two pipes
> > >> 16
> > >>
> > >> real    0m0.185s
> > >> user    0m0.010s
> > >> sys     0m0.100s
> > >>
> > >> thartman at linodewhyou:~/learning/haskell/UnixTools$
> > >>
> > >>
> > >> thartman at linodewhyou:~/learning/haskell/UnixTools$ cat oneliners.sh
> > >> hmap (){ ghc -e "interact ($*)";  }
> > >> hmapl (){ hmap  "unlines.($*).lines" ; }
> > >> hmapw (){ hmapl "map (unwords.($*).words)" ; }
> > >>
> > >> function filesizes () {
> > >>  find -maxdepth 1 -type f | xargs du
> > >> }
> > >>
> > >> echo haskell, ghc -e pipe
> > >> time filesizes | ghc -e 'interact $ (++"\n") . show . sum . map ( (
> > >> read :: String -> Integer ) . head . words ) . lines '
> > >> echo "**********"
> > >>
> > >> echo haskell, hmap pipe
> > >> time filesizes | hmap '(++"\n") . show . sum . map ( ( read :: String
> > >> -> Integer ) . head . words ) . lines'
> > >> echo "**********"
> > >>
> > >> echo haskell, two pipes
> > >> time filesizes | hmapl "map ( head . words )" | hmap '(++"\n") . show
> > >> . sum . map ( read :: String -> Integer ) . lines'
> > >> echo "**********"
> > >>
> > >> echo perl, two pipes
> > >> time filesizes | perl -ane 'print "$F[0]\n"' | perl -e '$sum += $_
> > >> while <>; print "$sum\n"'
> > >>
> > >>
> > >> 2007/3/2, Thomas Hartman <tphyahoo at gmail.com>:
> > >> >Okay, I am aware of
> > >> >
> > >> >http://haskell.org/haskellwiki/Simple_unix_tools
> > >> >
> > >> >which gives some implementation of simple unix utilities in haskell.
> > >> >
> > >> >But I couldn't figure out how to use them directly from the shell, and
> > >> >of course that's what most readers will probably wnat.
> > >> >
> > >> >Or let me put it another way.
> > >> >
> > >> >Is there a way to do
> > >> >
> > >> >  find -maxdepth 1 -type f | xargs du | perl -ane 'print "\$F[0]\n"' |
> > >> >perl -e '$sum += $_ while <>; print "$sum\n"'
> > >> >
> > >> >as a shell command that idiomatically uses haskell?
> > >> >
> > >> >For non-perlers, that sums up the disk usage of all files in the
> > >> >current directory, skipping subdirs.
> > >> >
> > >> >print "\$F[0]\n
> > >> >
> > >> >looks at the first (space delimited) collumn of output.
> > >> >
> > >> >perl -e '$sum += $_ while <>; print "$sum\n"'
> > >> >
> > >> >, which is I guess the meat of the program, sums up all the numbers
> > >> >spewed out of the first column, so in the end you get a total.
> > >> >
> > >> >So, anyone out there want to establish a haskell one liner tradition?
> > >> >
> > >> >:)
> > >> >
> > >> >thomas.
> > >> >
> > >> _______________________________________________
> > >> Haskell-Cafe mailing list
> > >> Haskell-Cafe at haskell.org
> > >> http://www.haskell.org/mailman/listinfo/haskell-cafe
> > >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list