Same thing, but with better comments and whitespace.

[EMAIL PROTECTED]:~/learning/haskell/UnixTools>head -n30 sortNumeric.sh
cat out_select_char_length_csv.out | ghc -e '
interact $
   unlines

       -- take 10 from the end
       -- more efficient than
       -- reverse . take 10 . reverse
       . ( \s -> drop (length s - 10 ) s )

       . map show -- convert Integer to String

           -- sort numerically
           . Data.List.sort

       . map ( read :: String -> Integer ) -- convert String to Integer

       -- Uniqify
       -- more efficient than prelude nub
       -- sorts too, but alphanumerically, whereas we want numerically
       . Data.Set.toAscList . Data.Set.fromList

       . filter ( all Data.Char.isDigit )

   . lines
'


2007/3/20, Thomas Hartman <[EMAIL PROTECTED]>:
To answer my own post, the Data.List.sort *is* necessary.

Otherwise, you get alphabetic sort.

2007/3/20, Thomas Hartman <[EMAIL PROTECTED]>:
> Just thought I'd add another potentially helpful bit to this oneliner
> / shell scripting thread. Though to be fair, this perhaps strains the
> definition of "one" in "one liner".
>
> This takes a long file containing mostly numerical data, filters out
> the numerical data, and sorts it numerically. (Not the same thing as
> sorting alphabetically, which is what you get by default, or using the
> unix sort utility). Maybe there's some flag to make unix sort util act
> like this? Enh, who cares, now we have haskell. :)
>
> Thanks to Thunder, Quicksilver, and whoever else it was on #haskell
> who helped me out with this.
>
> ******************************************************
>
> [EMAIL PROTECTED]:~/learning/haskell/UnixTools>cat sortNumeric.sh | head -n10
> cat out_select_char_length_csv.out | ghc -e '
> interact $
> unlines
> . map show
>
> -- more efficient than -- reverse . take 10 . reverse
> . ( \s -> drop (length s - 10 ) s )
>
> . Data.List.sort -- maybe not necessary?
> . map ( read :: String -> Integer )
> . Data.Set.toAscList . Data.Set.fromList -- more efficient than prelude nub
> . filter ( all Data.Char.isDigit ) . lines'
>
> 2007/3/7, Chris Kuklewicz <[EMAIL PROTECTED]>:
> > Thomas Hartman wrote:
> > > Just noticed a comment in
> > >
> > > 
http://www.serpentine.com/blog/2007/02/27/a-haskell-regular-expression-tutorial/
> > >
> > >
> > > which says there's no perl-like regex replace in the library, and links to
> > >
> > > http://hpaste.org/697
> > >
> > > which is an attempt at providing one.
> > >
> > > Not sure if this is useful or not.
> > >
> >
> > Any given replacement routine is less than 10 lines of code and will do 
exactly
> > what you need.
> >
> > A general replacement library has to contend with several things:
> >   1a) What syntax/semantics?
> >   1b) How do you supply a specification?  Must it be the same type as the
> > regular expression or the data?
> >   1c) How do you report errors?
> >   2) Which regex-* backends to support?
> >   3) What types to work on? [Char], Seq Char, ByteString, Lazy ByteString.
> >   4a) If the backend/type supports lazy matching then does the replacing?
> >   4b) What if the backend/type does not support lazy match or strictness is 
desired?
> >   5) If there is laziness then can it handle infinite streams of input?
> >   6) Is anyone smart enough to design this API without actual users?
> >
> > Note that some approaches allow for much more efficiency than others.  
Taking a
> > normal ByteString and performing replacement to create a Lazy ByteString 
makes
> > sense, but is a bit of wrinkle.
> >
> > But as you pointed to on http://hpaste.org/697 any given example of a
> > replacement routine will be very small, and easy to build on top of the 
regex-* API.
> >
>

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to