Kernighans large earthquake problem

From Rosetta Code
Task
Kernighans large earthquake problem
You are encouraged to solve this task according to the task description, using any language you may know.

Brian Kernighan, in a lecture at the University of Nottingham, described a problem on which this task is based.

Problem

You are given a a data file of thousands of lines; each of three `whitespace` separated fields: a date, a one word name and the magnitude of the event.

Example lines from the file would be lines like:

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1
Task
  • Create a program or script invocation to find all the events with magnitude greater than 6
  • Assuming an appropriate name e.g. "data.txt" for the file:
  1. Either: Show how your program is invoked to process a data file of that name.
  2. Or: Incorporate the file name into the program, (as it is assumed that the program is single use).



11l

Translation of: Python
L(ln) File(‘data.txt’).read_lines()
   I Float(ln.split(‘ ’, group_delimiters' 1B)[2]) > 6
      print(ln)
Output:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

68000 Assembly

I'm going to make the assumption that all magnitudes are given as floating points rounded to one decimal place, e.g. "6.0" when the magnitude is exactly 6. That way I don't need to actually use floating point logic. The hardware print routines were omitted to keep things short, since the Sega Genesis doesn't have a built-in kernel and so I'd have to manually write to the video chip. Chances are you're not interested in seeing all that fluff when you'd rather look at the actual algorithm for the task.

;Macros
	macro pushRegs 1
		MOVEM.L \1,-(SP)
	endm
;---------------------------------------------------------------------------
	macro popRegs 1
		MOVEM.L (SP)+,\1
	endm
;---------------------------------------------------------------------------

;Ram Variables
ramArea equ $00FF0000
Cursor_X equ ramArea	;Ram for Cursor Xpos
Cursor_Y equ ramArea+1	;Ram for Cursor Ypos


;cartridge header and init routine go here, I'll leave them out to keep things short. Execution falls through into here
;after the screen has been activated and the bitmap font loaded into VRAM


        LEA earthquake,A3
	move.l #3-1,d7			;total line count in the file.
mainloop:
	MOVE.B #'.',D0			;find the period in each line.
	MOVE.B #10,D1
	jsr CharInThisLine
	CMP.B #255,D0
	BNE foundIt
	jsr lineseek
	jmp mainloop
foundIt:
	;print only if magnitude is 6.1 or greater
	suba.l #2,a4
	cmp.b #'6',(a4)
	bcs .skip
		adda.l #2,a4
		cmp.b #'0',(a4)
		beq .skip
		jsr printline
.skip:
	DBRA D7,mainloop
	
	jmp *						;end program
	
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; unixdict functions:
PrintLine:
		MOVE.B (A3)+,D0
		CMP.B #10,D0
		BEQ .done
		CMP.B #255,D0
		BEQ .done
		jsr PrintChar
		bra PrintLine
.done:
	ADDA.L #1,A0 ;inc past the line feed to the next word.
	;fallthrough is intentional here
NewLine:
	addq.b #1,(Cursor_Y)		;INC Y
	clr.b (Cursor_X)		;Zero X
	rts	
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
IgnoreCase:
;forces lower case.
;input: d0.b
;output: d0.b
	CMP.B #'A',D0       ;compare to ascii code for A
	BCS .done      		;if less than A, keep looping.
 
	CMP.B #'Z'+1,D0       ;compare to ascii code for Z
	BCC .done      		;if greater than Z, keep looping
 
	OR.B #%00100000,D0  ;this "magic constant" turns upper case to lower case, since they're always 32 apart.
.done
	RTS
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
CharInThisLine:
	pushregs d2-d4/a3
		;input: d0 = char to search for. d1 = terminator of choice
		MOVEQ #0,D3
.again:
		MOVE.B (A3)+,D2
		CMP.B D1,D2
		BEQ .didntFindIt
		pushlong d0
			move.b d2,d0
			jsr ignoreCase
			move.b d0,d2
		poplong d0
		CMP.B D0,D2
		BEQ .foundIt
		addq.l #1,d3
		bra .again
		
.didntFindIt:
		MOVE.B #255,D0		;RETURN 255 ON FAILURE
		bra .exit
.foundIt:
		MOVE.L D3,D0		;RETURN ZERO-INDEXED POSITION OF CHAR ON SUCCESS
		bra .exit
		
.exit:
	move.l a3,a4
	popregs d2-d4/a3
	rts
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
lineseek:
;advances pointer to the "next" word without printing anything.
		MOVE.B (A3)+,D0
		CMP.B #10,D0
		BEQ .done
		CMP.B #255,D0
		BEQ .done
		bra lineseek
.done:
	RTS
Output:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

8080 Assembly

Say what you want about language design, but assembly does let you cut down the work done to the absolute minimum. This program can process a file of arbitrary size on a machine from the 1970s about as quickly as the disk can supply the bytes, needing no more working memory than the size of one line plus four bytes of stack space.

The file is given on the command line, because that way CP/M will set up an FCB automatically.

FCB1:	equ	5Ch	; FCB for first command line argument	
puts:	equ	9	; CP/M syscall to print a string
fopen:	equ	15	; CP/M syscall to open a file
fread:	equ	20	; CP/M syscall to read a block from a file
dta:	equ	80h	; Default disk transfer address
	org	100h
	lxi	d,FCB1	; Try to open the file given on the command line
	mvi	c,fopen
	call	5
	inr	a	; A = 0 = error
	jz	err	
	lxi	h,line	; Start of line buffer
block:	push	h	; Keep line buffer pointer
	lxi	d,FCB1	; Read a block from the file
	mvi	c,fread
	call	5
	pop	h	; Restore line buffer pointer
	dcr	a	; A = 1 = end of file (done)
	rz
	inr	a	; otherwise, A <> 0 = read error
	jnz	err
	lxi	d,dta	; Start of block
char:	ldax	d	; Grab character from block
	mov	m,a	; Store in line buffer
	inx	h	; Advance line buffer pointer
	cpi	10	; End of line?
	cz	doline	; Then handle the line
	inr	e	; Next character in block
	jz	block	; Rollover = get new block
	jmp	char 	; Otherwise = get next char
	;;;	Handle a line
doline:	push	d	; Keep block pointer
	mvi	m,'$'	; Terminate line buffer with CP/M end-of-string marker
	mvi	a,32
scan1:	dcx	h	; Scan backwards from end of line until we find
	cmp	m	; a non-control/whitespace character
	jnc	scan1	; (this makes it newline-format agnostic)
scan2:	dcx	h	; Then scan backwards until we _do_ find whitespace
	cmp	m	; This should leave us pointing right before the number
	jc	scan2
	inx	h	; First digit - we can cheat a little since we know
	mov	a,m	; earthquakes >=10 are physically impossible
	cpi	'7'	; If 7 or larger we know we should print it
	jnc	print
	cpi	'6' 	; If smaller than 6 we know we mustn't print it
	jc	next
	inx	h	; If 6, we must check fractional part
	mov	a,m
	cpi	'.'	; If no fractional part, then it is exactly 6 so
	jnz	next	; we shouldn't print it
scan3:	inx	h
	mov	a,m
	cpi	'$'	; If we reach the end, don't print it
	jz	next
	cpi	'1' 	; But if fractional part > 0, do print it
	jc	scan3
print:	lxi	d,line	; Print the line
	mvi	c,puts
	call	5
next:	pop	d	; Restore block pointer
	lxi	h,line	; Put line buffer pointer back at beginning
	ret
err:	lxi	d,emsg	; Print error message and stop
	mvi	c,puts
	jmp	5
emsg:	db	'Error!$'
line:	equ	$	; Line buffer after program
Output:
A>type data.txt
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1
1/23/4567    EdgeCase1           6
1/24/4567    EdgeCase2           6.0
1/25/4567    EdgeCase3           6.1

A>quakes data.txt
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
1/25/4567    EdgeCase3           6.1

Action!

In the following solution the input file quakes.txt is loaded from H6 drive. Altirra emulator automatically converts CR/LF character from ASCII into 155 character in ATASCII charset used by Atari 8-bit computer when one from H6-H10 hard drive under DOS 2.5 is used.

INCLUDE "H6:REALMATH.ACT"

BYTE FUNC FindFirstNonspace(CHAR ARRAY s BYTE start)
  WHILE start<=s(0) AND s(start)=32
  DO
    start==+1
  OD
RETURN (start)

BYTE FUNC FindFirstSpace(CHAR ARRAY s BYTE start)
  WHILE start<=s(0) AND s(start)#32
  DO
    start==+1
  OD
RETURN (start)

BYTE FUNC Found(CHAR ARRAY s REAL POINTER value)
  BYTE pos,v
  CHAR ARRAY sub

  pos=FindFirstNonspace(s,1)
  pos=FindFirstSpace(s,pos)
  pos=FindFirstNonspace(s,pos)
  pos=FindFirstSpace(s,pos)
  pos=FindFirstNonspace(s,pos)
  IF pos>s(0) THEN RETURN (0) FI

  SCopyS(sub,s,pos,s(0))
  ValR(sub,v)
  IF RealGreaterOrEqual(value,v)=0 THEN
    RETURN (1)
  FI
RETURN (0)

PROC Process(CHAR ARRAY fname REAL POINTER value BYTE search)
  CHAR ARRAY line(255)
  BYTE dev=[1]

  Close(dev)
  Open(dev,fname,4)
  WHILE Eof(dev)=0
  DO
    InputSD(dev,line)
    IF search=0 OR Found(line,value)=1 THEN
      PrintE(line)
    FI
  OD
  Close(dev)
RETURN

PROC Main()
  CHAR ARRAY fname="H6:QUAKES.TXT"
  REAL value

  Put(125) PutE() ;clear the screen
  IntToReal(6,value)
  PrintF("Reading ""%S""...%E%E",fname)
  Process(fname,value,0)
  PutE()
  Print("Searching for earthquakes > ")
  PrintRE(value) PutE()
  Process(fname,value,1)
RETURN
Output:

Screenshot from Atari 8-bit computer

Reading "H6:QUAKES.TXT"...

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1
1/23/4567    EdgeCase1           6



1/24/4567    EdgeCase2           6.0
1/25/4567    EdgeCase3           6.1


Searching for earthquakes > 6

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
1/25/4567    EdgeCase3           6.1

Ada

-- Kernighans large earthquake problem
with Ada.Text_IO;       use Ada.Text_IO;
with Ada.Strings.Fixed; use Ada.Strings.Fixed;
use Ada.Strings;

procedure Main is
   Inpt_File : File_Type;
   Space     : Natural;
begin
   Open (File => Inpt_File, Mode => In_File, Name => "data.txt");
   while not End_Of_File (Inpt_File) loop
      declare
         Line : String :=
           Trim (Source => Get_Line (File => Inpt_File), Side => Both);
      begin

         if Line'Length > 0 then
            Space := Line'Last;
            loop
               exit when Line (Space) = ' ' or else Space = 0;
               Space := Space - 1;
            end loop;

            if Space > 0 then
               if Float'Value (Line (Space .. Line'Last)) > 6.0 then
                  Put_Line (Line);
               end if;
            end if;
         end if;
      end;
   end loop;
   Close (Inpt_File);
end Main;

The file data.txt contains a 0 length line as well as a line composed of only blanks.

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1
1/23/4567    EdgeCase1           6

                                          
1/24/4567    EdgeCase2           6.0
1/25/4567    EdgeCase3           6.1
Output:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
1/25/4567    EdgeCase3           6.1

ALGOL 68

IF  FILE input file;
    STRING file name = "data.txt";
    open( input file, file name, stand in channel ) /= 0
THEN
    # failed to open the file #
    print( ( "Unable to open """ + file name + """", newline ) )
ELSE
    # file opened OK #
    BOOL at eof := FALSE;
    # set the EOF handler for the file #
    on logical file end( input file, ( REF FILE f )BOOL:
                                     BEGIN
                                         # note that we reached EOF on the latest read #
                                         at eof := TRUE;
                                         # return TRUE so processing can continue #
                                         TRUE
                                     END
                       );
    # return the real value of the specified field on the line #
    PROC real field = ( STRING line, INT field )REAL:
         BEGIN
            REAL result  := 0;
            INT  c pos   := LWB line;
            INT  max pos := UPB line;
            STRING f     := "";
            FOR f ield number TO field WHILE c pos <= max pos DO
                # skip leading spaces #
                WHILE IF c pos > max pos THEN FALSE ELSE line[ c pos ] = " " FI DO
                    c pos +:= 1
                OD;
                IF c pos <= max pos THEN
                    # have a field #
                    INT start pos = c pos;
                    WHILE IF c pos > max pos THEN FALSE ELSE line[ c pos ] /= " " FI DO
                        c pos +:= 1
                    OD;
                    IF field number = field THEN
                        # have the required field #
                        f := line[ start pos : c pos - 1 ]
                    FI
                FI
            OD;
            IF f /= "" THEN
                # have the field - assume it a real value and convert it #
                FILE real value;
                associate( real value, f );
                on value error( real value
                              , ( REF FILE f )BOOL:
                                     BEGIN
                                         # "handle" invalid data #
                                         result := 0;
                                         # return TRUE so processing can continue #
                                         TRUE
                                     END
                              );
                get( real value, ( result ) )
            FI;
            result
         END # real field # ;
    # show the lines where the third field is > 6 #
    WHILE NOT at eof
    DO
        STRING line;
        get( input file, ( line, newline ) );
        IF real field( line, 3 ) > 6 THEN
            print( ( line, newline ) )
        FI
    OD;
    # close the file #
    close( input file )
FI

Amazing Hopper

/* Kernighans large earthquake problem. */

#include <flow.h>
#include <flow-flow.h>

#define MAX_LINE 1000

DEF-MAIN(argv,argc)
   MSET(fd, Event )
   TOK-INIT
   OPEN-INPUT("datos.txt")(fd)
   COND( IS-NOT-FILE-ERROR? )
      TOK-SEP( " " ), TOK(3)
      WHILE( NOT( EOF(fd) ) )
         LET( Event := USING(MAX_LINE) READ-LINE(fd) APPLY-TRM )
         WHEN( LEN(Event) ){
            WHEN( GT?( VAL(TOK-GET(Event)), 6 ) ){
               PRNL( Event )
            }
         }
      WEND
      CLOSE(fd)
   ELS
      PRNL("Error: ", ~GET-STR-FILE-ERROR )
   CEND
END
Output:
Data file: datos.txt.

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1
1/23/4567    EdgeCase1           6

                                          
1/24/4567    EdgeCase2           6.0
1/25/4567    EdgeCase3           6.1

Output:

$ hopper fl/evento.flw
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
1/25/4567    EdgeCase3           6.1
$

PROBLEM: What if the file contains more information than expected? We would have to validate the lines that can be processed. For example, we might have a file with the following information:

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1
Total events: 3

1/23/4567    EdgeCase1           6

                                          
1/24/4567    EdgeCase2           6.0
1/25/4567    EdgeCase3           6.1
1/25/4567    EdgeCase4           6.1
Total events: 4

Total Events in periods: 7

There are lines with 3 tokens, and the third token is numeric: it would be shown as a valid record!

On the other hand, HOPPER processes dates in DD/MM/YYYY format, and the file records dates in MM/DD/YYYY format: therefore, it is necessary to exchange "DD" for "MM", because HOPPER does not allow other types of format for "dates".

The final program would be as follows:

/* Kernighans large earthquake problem. */

#include <flow.h>
#include <flow-flow.h>

#define MAX_LINE                  1000
#define SwapDayByMonth(_N_,_M_)   TOK-SEP("/"), TOK(_N_), TOK-SWAP(_M_,Event), TOK-SEP(" ")

DEF-MAIN(argv,argc)
   MSET(fd, Event )
   TOK-INIT
   OPEN-INPUT("datos.txt")(fd)
   COND( IS-NOT-FILE-ERROR? )
      TOK-SEP( " " )
      WHILE( NOT( EOF(fd) ) )
         LET( Event := USING(MAX_LINE) READ-LINE(fd) APPLY-TRM )
         WHEN( LEN(Event) ){
            WHEN( EQ?(TOK-COUNT( Event ),3) ){
               Swap Day By Month(1,2)
               WHEN( IS-DATE-VALID?( TOK(1) TOK-GET(Event) )){
                  TOK(3)
                  WHEN( GT?( VAL(TOK-GET(Event)), 6 ) ){
                     PRNL( Event )
                  }
               }
            }
         }
      WEND
      CLOSE(fd)
   ELS
      PRNL("Error: ", ~GET-STR-FILE-ERROR )
   CEND
END

And this is fast!

If you want to print the original dates, just add the line "Swap Day By Month(1,2)" before printing the result. In this case, the results are printed with the dates changed.

Output:
27/8/1883    Krakatoa            8.8
18/5/1980    MountStHelens       7.6
25/1/4567    EdgeCase3           6.1
25/1/4567    EdgeCase4           6.1

AppleScript

on kernighansEarthquakes(magnitudeToBeat)
    -- A local "owner" for the long AppleScript lists. Speeds up references to their items and properties.
    script o
        property individualEntries : {}
        property qualifyingEntries : {}
    end script
    
    -- Read the text file assuming it's UTF-8 encoded and get a list of the individual entries.
    set textFilePath to (path to desktop as text) & "data.txt"
    set earthquakeData to (read file textFilePath as «class utf8»)
    set o's individualEntries to earthquakeData's paragraphs
    -- Get the input magnitude in text form now rather than coercing it during the repeat.
    set magnitudeToBeat to magnitudeToBeat as text
    
    -- Check the entries with AppleScript's text item delimiters set to likely white space characters and considering numeric strings.
    -- With these delimiters, the entries' magnitudes will be the last 'text item' in each line
    -- (assuming for this exercise that there'll never be white space at the end of any of the lines).
    -- Store entries with qualifying magnitudes in a new list.
    set astid to AppleScript's text item delimiters
    set AppleScript's text item delimiters to {space, tab, character id 160} -- White space characters.
    considering numeric strings -- Compare numbers in strings numerically instead of lexically.
        repeat with i from 1 to (count o's individualEntries)
            set thisEntry to item i of o's individualEntries
            if (thisEntry's last text item > magnitudeToBeat) then set end of o's qualifyingEntries to thisEntry
        end repeat
    end considering
    
    -- Coerce the list of qualifying earthquakes to a single, linefeed-delimited text and return the result.
    set AppleScript's text item delimiters to linefeed
    set largeEarthquakes to o's qualifyingEntries as text
    set AppleScript's text item delimiters to astid
    
    return largeEarthquakes
end kernighansEarthquakes

kernighansEarthquakes(6)

Functional

Checking that the file exists, and discarding any blank lines, while emphasising code reuse, and speed of writing and refactoring:

use AppleScript version "2.4"
use framework "Foundation"
use scripting additions

property magnitude : 6.0
property fp : "~/Desktop/data.txt"


-------------------------- TEST ---------------------------
on run
    
    either(identity, identity, ¬
        bindLR(readFileLR(fp), ¬
            report(fp, magnitude)))
    
end run


-------------------- EARTHQUAKE REPORT --------------------

-- report :: FilePath -> Float -> String -> String
on report(fp, threshold)
    script
        on |λ|(s)
            |Right|(unlines({("Magnitudes above " & magnitude as string) & ¬
                " in " & fp & ":", ""} & ¬
                concatMap(aboveThreshold(threshold), paragraphs of s)))
        end |λ|
    end script
end report


-- aboveThreshold :: Float -> String -> Bool
on aboveThreshold(threshold)
    script
        on |λ|(s)
            if ""  s and threshold < (item -1 of words of s) as number then
                {s}
            else
                {}
            end if
        end |λ|
    end script
end aboveThreshold


-------------------- REUSABLE GENERICS --------------------

-- Left :: a -> Either a b
on |Left|(x)
    {type:"Either", |Left|:x, |Right|:missing value}
end |Left|


-- Right :: b -> Either a b
on |Right|(x)
    {type:"Either", |Left|:missing value, |Right|:x}
end |Right|


-- bindLR (>>=) :: Either a -> (a -> Either b) -> Either b
on bindLR(m, mf)
    if missing value is not |Left| of m then
        m
    else
        mReturn(mf)'s |λ|(|Right| of m)
    end if
end bindLR


-- concatMap :: (a -> [b]) -> [a] -> [b]
on concatMap(f, xs)
    set lng to length of xs
    set acc to {}
    tell mReturn(f)
        repeat with i from 1 to lng
            set acc to acc & (|λ|(item i of xs, i, xs))
        end repeat
    end tell
    return acc
end concatMap


-- either :: (a -> c) -> (b -> c) -> Either a b -> c
on either(lf, rf, e)
    if missing value is |Left| of e then
        tell mReturn(rf) to |λ|(|Right| of e)
    else
        tell mReturn(lf) to |λ|(|Left| of e)
    end if
end either


-- identity :: a -> a
on identity(x)
    -- The argument unchanged.
    x
end identity


-- mReturn :: First-class m => (a -> b) -> m (a -> b)
on mReturn(f)
    -- 2nd class handler function lifted into 1st class script wrapper. 
    if script is class of f then
        f
    else
        script
            property |λ| : f
        end script
    end if
end mReturn


-- readFileLR :: FilePath -> Either String IO String
on readFileLR(strPath)
    set ca to current application
    set e to reference
    set {s, e} to (ca's NSString's ¬
        stringWithContentsOfFile:((ca's NSString's ¬
            stringWithString:strPath)'s ¬
            stringByStandardizingPath) ¬
            encoding:(ca's NSUTF8StringEncoding) |error|:(e))
    if s is missing value then
        |Left|((localizedDescription of e) as string)
    else
        |Right|(s as string)
    end if
end readFileLR


-- unlines :: [String] -> String
on unlines(xs)
    -- A single string formed by the intercalation
    -- of a list of strings with the newline character.
    set {dlm, my text item delimiters} to ¬
        {my text item delimiters, linefeed}
    set str to xs as text
    set my text item delimiters to dlm
    str
end unlines
Output:
Magnitudes above 6.0 in ~/Desktop/data.txt:

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

APL

Works with: Dyalog APL

This runs from the APL prompt, taking the filename as the right argument and the magnitude as an optional left argument (defaulting to 6).

quakes{
    6
    nl⎕UCS 13 10
    file80 ¯1⎕MAP 
    lines((~filenl)file)~¨nl
    keep{0::0   < 3(~4⎕TC)}¨lines
    keep/lines
}
Output:
      quakes'data.txt'
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
      5 quakes'data.txt'
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1
      8 quakes'data.txt'
8/27/1883    Krakatoa            8.8

Arturo

data: {
    3/13/2009    CostaRica           5.1
    8/27/1883    Krakatoa            8.8
    5/18/1980    MountStHelens       7.6
}

define :earthquake [date place magnitude][]

print first sort.descending.by:'magnitude map split.lines data => 
    [to :earthquake split.words &]
Output:
[date:8/27/1883 place:Krakatoa magnitude:8.8]

AWK

 awk '$3 > 6' data.txt

Bash

#!/bin/bash
while read line 
do
    [[ ${line##* } =~ ^([7-9]|6\.0*[1-9]).*$ ]] && echo "$line"
done < data.txt
Output:
$ cat data.txt
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1
1/23/4567    EdgeCase1           6
1/24/4567    EdgeCase2           6.0
1/25/4567    EdgeCase3           6.1
$ bash quake.sh
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
1/25/4567    EdgeCase3           6.1


BASIC256

f = freefile
filename$ = "data.txt"
open f, filename$

dim tok$(1)
while not eof(f)
	tok$[] = readline(f)
	if (right(tok$[], 4)) > 6 then print tok$[]
end while
close f
end


C

#include <stdio.h>
#include <string.h>
#include <stdlib.h>

int main() {
    FILE *fp;
    char *line = NULL;
    size_t len = 0;
    ssize_t read;
    char *lw, *lt;
    fp = fopen("data.txt", "r");
    if (fp == NULL) {
        printf("Unable to open file\n");
        exit(1);
    }
    printf("Those earthquakes with a magnitude > 6.0 are:\n\n");
    while ((read = getline(&line, &len, fp)) != EOF) {
        if (read < 2) continue;   /* ignore blank lines */
        lw = strrchr(line, ' ');  /* look for last space */
        lt = strrchr(line, '\t'); /* look for last tab */
        if (!lw && !lt) continue; /* ignore lines with no whitespace */
        if (lt > lw) lw = lt;     /* lw points to last space or tab */
        if (atof(lw + 1) > 6.0) printf("%s", line);
    }
    fclose(fp);
    if (line) free(line);
    return 0;
}
Output:

Using the given file:

Those earthquakes with a magnitude > 6.0 are:

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

C#

using System;
using System.IO;
using System.Linq;
using System.Collections.Generic;

public class Program
{
    static void Main() {
        foreach (var earthquake in LargeEarthquakes("data.txt", 6))
            Console.WriteLine(string.Join(" ", earthquake));
    }

    static IEnumerable<string[]> LargeEarthquakes(string filename, double limit) =>
        from line in File.ReadLines(filename)
        let parts = line.Split(default(char[]), StringSplitOptions.RemoveEmptyEntries)
        where double.Parse(parts[2]) > limit
        select parts;

}

C++

// Randizo was here!
#include <iostream>
#include <fstream>
#include <string>
using namespace std;

int main()
{
    ifstream file("../include/earthquake.txt");

    int count_quake = 0;
    int column = 1;
    string value;
    double size_quake;
    string row = "";


    while(file >> value)
    {
        if(column == 3)
        {
            size_quake = stod(value);

            if(size_quake>6.0)
            {
                count_quake++;
                row += value + "\t";
                cout << row << endl;
            }

            column = 1;
            row = "";
        }
        else
        {
            column++;
            row+=value + "\t";
        }
    }

    cout << "\nNumber of quakes greater than 6 is " << count_quake << endl;

    return 0;
}

New version:

// Jolkdarr was also here!
#include <iostream>
#include <iomanip>
#include <fstream>
#include <string>

int main() {
    using namespace std;
    ifstream file("data.txt");
    int count_quake = 0;
    string s1, s2;
    double rate;
    while (!file.eof()) {
        file >> s1 >> s2 >> rate;
        if (rate > 6.0) {
            cout << s1 << setw(20) << s2 << " " << rate << endl;
            count_quake++;
        }
    }

    cout << endl << "Number of quakes greater than 6 is " << count_quake << endl;
    return 0;
}

Cixl

use: cx;

'data.txt' `r fopen lines {
  let: (time place mag) @@s split ..;
  let: (m1 m2) $mag @. split &int map ..;
  $m1 6 >= $m2 0 > and {[$time @@s $place @@s $mag] say} if
} for
Output:
8/27/1883 Krakatoa 8.8
5/18/1980 MountStHelens 7.6

COBOL

First, with a data file. This adds a fair amount of verbosity to COBOL. For something this one-off, a simpler cut using ACCEPT from standard in is shown.

*>
*> Kernighan large earthquake problem
*> Tectonics: cobc -xj kernighan-earth-quakes.cob
*>            quakes.txt with the 3 sample lines
*>            ./kernighan-earth-quakes
*>
 >>SOURCE FORMAT IS FREE
 IDENTIFICATION DIVISION.
 PROGRAM-ID. quakes.

 ENVIRONMENT DIVISION.
 CONFIGURATION SECTION.
 REPOSITORY.
     FUNCTION ALL INTRINSIC.

 INPUT-OUTPUT SECTION.
 FILE-CONTROL.
     SELECT quake-data
         ASSIGN TO command-filename
         ORGANIZATION IS LINE SEQUENTIAL
         STATUS IS quake-fd-status.

 DATA DIVISION.
 FILE SECTION.
 FD quake-data RECORD VARYING DEPENDING ON line-length.
     01 data-line         PICTURE IS X(32768).

 WORKING-STORAGE SECTION.
 01 quake-fd-status       PICTURE IS XX.
    88 ok                 VALUES ARE "00", "01", "02", "03", "04",
                                     "05", "06", "07", "08", "09".
    88 no-more            VALUE IS "10".
    88 io-error           VALUE IS HIGH-VALUE.

 01 line-length           USAGE IS BINARY-LONG.
 
 01 date-time             PICTURE IS X(10).
 01 quake                 PICTURE IS X(20).
 01 magnitude             PICTURE IS 99V99.

 01 command-filename      PICTURE IS X(80).

 PROCEDURE DIVISION.
 show-big-ones.

     ACCEPT command-filename FROM COMMAND-LINE
     IF command-filename IS EQUAL TO SPACES THEN
         MOVE "data.txt" TO command-filename
     END-IF
    
     OPEN INPUT quake-data
     PERFORM status-check
     IF io-error THEN
         DISPLAY TRIM(command-filename) " not found" UPON SYSERR
         GOBACK
     END-IF
    
     READ quake-data
     PERFORM status-check
     PERFORM UNTIL no-more OR io-error
         UNSTRING data-line DELIMITED BY ALL SPACES
            INTO date-time quake magnitude
         END-UNSTRING
    
         IF magnitude IS GREATER THAN 6
             DISPLAY date-time SPACE quake SPACE magnitude
         END-IF
    
         READ quake-data
         PERFORM status-check
     END-PERFORM
    
     CLOSE quake-data
     PERFORM status-check
     GOBACK.
*>   ****

 status-check.
     IF NOT ok AND NOT no-more THEN   *> not normal status, bailing
         DISPLAY "io error: " quake-fd-status UPON SYSERR
         SET io-error TO TRUE
     END-IF
     EXIT PARAGRAPH.

 END PROGRAM quakes.
Output:
prompt$ cobc -x kernighans-large-earthquakes.cob
prompt$ ./kernighans-large-earthquakes quakes.txt
8/27/1883  Krakatoa             08.80
5/18/1980  MountStHelens        07.60
prompt$ cat quakes.txt
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1

A slighter shorter-version.

      *>
      *> Tectonics: ./kerighan-earth-quakes <quakes.txt
       IDENTIFICATION DIVISION.
       PROGRAM-ID. quakes.

       DATA DIVISION.

       WORKING-STORAGE SECTION.
       01 data-line             PICTURE IS X(32768).
          88 no-more            VALUE IS HIGH-VALUES.

       01 date-time             PICTURE IS X(10).
       01 quake                 PICTURE IS X(20).
       01 magnitude             PICTURE IS 99V99.

       PROCEDURE DIVISION.
       show-big-ones.

       ACCEPT data-line ON EXCEPTION SET no-more TO TRUE END-ACCEPT
       PERFORM UNTIL no-more
           UNSTRING data-line DELIMITED BY ALL SPACES
              INTO date-time quake magnitude
           END-UNSTRING

           IF magnitude IS GREATER THAN 6
               DISPLAY date-time SPACE quake SPACE magnitude
           END-IF

           ACCEPT data-line ON EXCEPTION SET no-more TO TRUE END-ACCEPT
       END-PERFORM

       GOBACK.
       END PROGRAM quakes.

That cut would be used as

prompt$ ./kernighans-large-earthquakes <quakes.txt

Cowgol

include "cowgol.coh";
include "file.coh";

# Process a file line by line
interface LineCb(line: [uint8]);
sub ForEachLine(fcb: [FCB], cb: LineCb) is
    var buf: uint8[256];
    var ptr := &buf[0];
    
    var length := FCBExt(fcb);
    while length != 0 loop
        var ch := FCBGetChar(fcb);
        [ptr] := ch;
        ptr := @next ptr;
        if ch == '\n' then
            [ptr] := 0;
            ptr := &buf[0];
            cb(&buf[0]);
        end if;
        length := length - 1;
    end loop;
end sub;

# Get magnitude from line
# Cowgol does not support floating point arithmetic, so the integer and 
# fractional parts are returned separately
sub magnitude(line: [uint8]): (i: uint8, frac: uint8) is
    i := 0;
    frac := 0;
    var col: uint8 := 1;
    var space: uint8 := 0;
    # scan ahead to 3rd column
    while col < 3 loop
        var ch := [line];
        line := @next line;
        if ch == 0 then break; end if;
        if ch <= ' ' then
            while ch <= ' ' and ch != 0 loop
                ch := [line];
                line := @next line;
            end loop;
            col := col + 1;
        end if;
    end loop;
    if ch == 0 then
        return; # no 3rd column
    end if;
    line := @prev line;
    
    var n: int32;
    var pos: [uint8];
    # grab integer part
    (n, pos) := AToI(line);
    if pos == line then
        return; # no value
    end if;
    i := n as uint8;
    if [pos] == '.' then
        # grab fractional part
        (n, pos) := AToI(@next pos);
        frac := n as uint8;
    end if;
end sub;

# Print any line that has a magnitude > 6
sub PrintIfGt6 implements LineCb is
    var i: uint8;
    var frac: uint8;
    (i, frac) := magnitude(line);
    if i > 6 or (i == 6 and frac > 0) then
        print(line);
    end if;
end sub;

# Open "data.txt" and scan each line
var quakes: FCB;
if FCBOpenIn(&quakes, "data.txt") != 0 then
    print("Error!\n");
    ExitWithError();
end if;

ForEachLine(&quakes, PrintIfGt6);
Output:
$ cat data.txt
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1
1/23/4567    EdgeCase1           6
1/24/4567    EdgeCase2           6.0
1/25/4567    EdgeCase3           6.1
$ ./quakes.386
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
1/25/4567    EdgeCase3           6.1


Delphi

Works with: Delphi version 6.0

This code takes advantage of the standard Delphi "TStringGrid" object to do most of the heavy lifting. It is initially used to read the earthquake file into memory, breaking it up into of individual lines as it goes. Then the individual fields are stored in structurs/records attached to the data. finally, the data is sorted by magnitude so the earthquakes of magnitudes greater than six can be extracted. Because the data is now neatly organized in memory, all kinds of other process could be done, including sorting it by date or location. To make the problem more realistic, I extracted actual earthquake data from the first few months of 2023. I've post the data for other people to test here: EarthQuakes.txt

{Structure used to contain all the earthquake data}

type TQuakeInfo = record
 Date: TDate;
 Name: string;
 Mag: double;
 end;
type PQuakeInfo = ^TQuakeInfo;

{Used to contain individual fields of the earthquake data}

type TStringArray = array of string;


function SortCompare(List: TStringList; Index1, Index2: Integer): Integer;
{Custom sort routine to sort data by magnitude }
var QI1,QI2: TQuakeInfo;
begin
QI1:=PQuakeInfo(List.Objects[Index1])^;
QI2:=PQuakeInfo(List.Objects[Index2])^;
Result:=Round(QI2.Mag*10)-Round(QI1.Mag*10);
end;

procedure GetFields(S: string; var SA: TStringArray);
{Extract the three fields from each row of data}
var I,F: integer;
begin
SetLength(SA,3);
for I:=0 to High(SA) do SA[I]:='';
F:=0;
for I:=1 to Length(S) do
 if S[I] in [#$09,#$20] then Inc(F)
 else SA[F]:=SA[F]+S[I];
end;

procedure AnalyzeEarthQuakes(Filename: string; Memo: TMemo);
{Read earhtquake data from specified file}
{Extract the individual fields and sort and display it}
var SL: TStringList;
var I: integer;
var S: string;
var FA: TStringArray;
var QI: PQuakeInfo;
begin
SL:=TStringList.Create;
try
{Read file, separating it into rows}
SL.LoadFromFile(Filename);
{Process each row}
for I:=0 to SL.Count-1 do
	begin
	S:=SL[I];
	{Separate row into fields}
	GetFields(S,FA);
	{Store data as objects in TStringList}
	New(QI);
	QI.Date:=StrToDate(FA[0]);
	QI.Name:=FA[1];
	QI.Mag:=StrToFloat(FA[2]);
	SL.Objects[I]:=TObject(QI);
	end;
{Sort data by magnitude}
SL.CustomSort(SortCompare);
{Display sorted data}
for I:=0 to SL.Count-1 do
	begin
	if PQuakeInfo(SL.Objects[I]).Mag<6 then break;
	S:=FormatDateTime('dd/mm/yyyy', PQuakeInfo(SL.Objects[I]).Date);
	S:=S+Format('  %-34s',[PQuakeInfo(SL.Objects[I]).Name]);
	S:=S+Format('  %5f',[PQuakeInfo(SL.Objects[I]).Mag]);
        Memo.Lines.Add(S);
	end;
{Dispose of memory}
finally
 for I:=0 to SL.Count-1 do Dispose(PQuakeInfo(SL.Objects[I]));
 SL.Free;
 end;
end;


procedure ShowEarthQuakes(Memo: TMemo);
begin
AnalyzeEarthQuakes('EarthQuakes.txt',Memo);
end;
Output:
06/02/2023  Turkey_Kahramanmaras                 7.80
09/01/2023  Indonesia_Maluku                     7.60
06/02/2023  Turkey_Kahramanmaras                 7.50
02/04/2023  Papua_New_Guinea_East_Sepik          7.00
16/03/2023  New_Zealand_Kermadec_Islands         7.00
18/01/2023  Indonesia_North_Maluku               7.00
14/04/2023  Indonesia_East_Java                  7.00
08/01/2023  Vanuatu_Sanma                        7.00
04/03/2023  New_Zealand_Kermadec_Islands         6.90
23/02/2023  Tajikistan_Gorno-Badakhshan          6.90
18/03/2023  Ecuador_Guayas                       6.80
20/01/2023  Argentina_Santiago_del_Estero        6.80
18/04/2023  South_of_theFiji_Islands             6.70
06/02/2023  Turkey_Gaziantep                     6.70
01/03/2023  Papua_New_Guinea_West_New_Britain    6.60
02/03/2023  Vanuatu_Sanma                        6.50
03/04/2023  Russia_Kamchatka_Krai                6.50
22/03/2023  Argentina_Jujuy                      6.50
21/03/2023  Afghanistan_Badakhshan               6.50
24/01/2023  Argentina_Santiago_del_Estero        6.40
19/04/2023  Papua_New_Guinea_West_New_Britain    6.30
16/01/2023  Japan_Bonin_Islands                  6.30
20/02/2023  Turkey_Hatay                         6.30
23/02/2023  Indonesia_North_Maluku               6.30
21/04/2023  Indonesia_Southeast_Sulawesi         6.30
14/03/2023  Papua_New_Guinea_Madang              6.30
30/03/2023  Chile_Maule                          6.30
04/04/2023  Panama_Chiriqu-                      6.30
25/02/2023  Papua_New_Guinea_West_New_Britain    6.20
04/04/2023  Philippines_Bicol                    6.20
27/03/2023  Solomon_Islands_Isabel               6.10
03/04/2023  Indonesia_North_Sumatra              6.10
17/02/2023  Indonesia_Maluku                     6.10
15/02/2023  Philippines_Bicol                    6.10
13/02/2023  New_Zealand_Kermadec_Islands         6.10
20/01/2023  France_Guadeloupe                    6.10
15/01/2023  Indonesia_Aceh                       6.10
28/03/2023  Japan_Hokkaido                       6.00
18/01/2023  Indonesia_Gorontalo                  6.00
01/02/2023  Philippines_Davao                    6.00
05/01/2023  Afghanistan_Badakhshan               6.00
26/01/2023  New_Zealand_Kermadec_Islands         6.00
06/02/2023  Turkey_Kahramanmaras                 6.00
06/02/2023  Turkey_Malatya                       6.00
25/02/2023  Japan_Hokkaido                       6.00
13/04/2023  Canada_British_Columbia              6.00

D

Translation of: Kotlin
import std.conv : to;
import std.regex : ctRegex, split;
import std.stdio : File, writeln;

void main() {
    auto ctr = ctRegex!"\\s+";

    writeln("Those earthquakes with a magnitude > 6.0 are:");
    foreach (line; File("data.txt").byLineCopy) {
        auto parts = split(line, ctr);
        if (parts[2].to!double > 6.0) {
            writeln(line);
        }
    }
}
Output:
Those earthquakes with a magnitude > 6.0 are:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

Emacs Lisp

(with-temp-buffer
  (insert-file-contents "data.txt")
  (goto-char (point-min))
  (while (not (eobp))
    (let* ((line (buffer-substring (line-beginning-position)
                                   (line-end-position)))
           (magn (nth 2 (split-string line "\\s-+"))))
      (when (> (string-to-number magn) 6.0)
        (message line)))
    (forward-line 1)))

Factor

lines is a convenience word that reads lines from standard input. If you don't want to type them all in yourself, it is suggested that you give the program a file to read. For example, on the Windows command line: factor kernighan.factor < earthquakes.txt

USING: io math math.parser prettyprint sequences splitting ;
IN: rosetta-code.kernighan

lines [ "\s" split last string>number 6 > ] filter .


FreeBASIC

Dim As Long f
f = Freefile
Dim As String nomArchivo = "data.txt"

If Open(nomArchivo For Input As #f)  Then
    Print "ERROR: No se pudo abrir " ; nomArchivo
    Sleep : End
End If

Dim As String tok(), lin
Do While Not Eof(f)
    Line Input #f, lin
    If Val(Right(lin, 3)) > 6 Then Print lin
Loop
Close #f
Sleep


Go

package main

import (
    "bufio"
    "fmt"
    "os"
    "strconv"
    "strings"
)

func main() {
    f, err := os.Open("data.txt")
    if err != nil {
        fmt.Println("Unable to open the file")
        return
    }
    defer f.Close()
    fmt.Println("Those earthquakes with a magnitude > 6.0 are:\n")
    input := bufio.NewScanner(f)
    for input.Scan() {
        line := input.Text()
        fields := strings.Fields(line)
        mag, err := strconv.ParseFloat(fields[2], 64)
        if err != nil {
            fmt.Println("Unable to parse magnitude of an earthquake")
            return
        }
        if mag > 6.0 {
            fmt.Println(line)
        }
    }
}
Output:
Those earthquakes with a magnitude > 6.0 are:

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

Groovy

Translation of: Kotlin
import java.util.regex.Pattern

class LargeEarthquake {
    static void main(String[] args) {
        def r = Pattern.compile("\\s+")
        println("Those earthquakes with a magnitude > 6.0 are:\n")
        def f = new File("data.txt")
        f.eachLine { it ->
            if (r.split(it)[2].toDouble() > 6.0) {
                println(it)
            }
        }
    }
}
Output:
Those earthquakes with a magnitude > 6.0 are:

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

Haskell

import qualified Data.ByteString.Lazy.Char8 as C

main :: IO ()
main = do
  cs <- C.readFile "data.txt"
  mapM_ print $
    C.lines cs >>=
    (\x ->
        [ x
        | 6 < (read (last (C.unpack <$> C.words x)) :: Float) ])
Output:
"8/27/1883    Krakatoa            8.8"
"5/18/1980    MountStHelens       7.6"

J

NB. this program is designed for systems where the line ending is either LF or CRLF


NB. filename select_magnitude minimum
NB. default file is /tmp/famous.quakers

select_magnitude=: '/tmp/famous.quakers'&$: : (4 :0)
 data =. 1!:1 boxopen x       NB. read the file
 data =. data -. CR           NB. remove nasty carriage returns
 data =. ,&LF^:(LF~:{:) data  NB. append new line if none found
 lines =. [;._2 data          NB. split the literal based on the final character
 magnitudes =. ". _1&{::@(<;._2)@(,&' ')@deb"1 lines
 (y <: magnitudes) # lines
)
   select_magnitude 6
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

Java

Input file contains sample data shown in the task

import java.io.BufferedReader;
import java.io.FileReader;

public class KernighansLargeEarthquakeProblem {

    public static void main(String[] args) throws Exception {
        try (BufferedReader reader  = new BufferedReader(new FileReader("data.txt")); ) {
            String inLine = null;
            while ( (inLine = reader.readLine()) != null ) {
                String[] split = inLine.split("\\s+");
                double magnitude = Double.parseDouble(split[2]);
                if ( magnitude > 6 ) {
                    System.out.println(inLine);
                }
            }
        }

    }

}
Output:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

JavaScript

Input file contains sample data shown in the task. The code below uses Nodejs to read the file.

const fs = require("fs");
const readline = require("readline");

const args = process.argv.slice(2);
if (!args.length) {
    console.error("must supply file name");
    process.exit(1);
}

const fname = args[0];

const readInterface = readline.createInterface({
    input: fs.createReadStream(fname),
    console: false,
});

readInterface.on("line", (line) => {
    const fields = line.split(/\s+/);
    if (+fields[fields.length - 1] > 6) {
        console.log(line);
    }
});
Output:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

jq

Works with: jq

Works with gojq, the Go implementation of jq

To meet the task requirements in a minimal way, one could invoke jq as follows:

jq -Rrn 'inputs | . as $line | [splits("  *") ] | select((.[2]|tonumber) > 6) | $line' data.txt

The program shown in the following subsection, by contrast, determines the file name dynamically and includes some error-checking. The output shown below is based on the invocation:

jq -Rrn -f large-earthquake-problem.jq data.txt

where data.txt is as for Snobol.

input as $one
| "The earthquakes from \(input_filename) with a magnitude greater than 6 are:\n",
( $one, inputs
  | . as $line
  | [splits("  *")]
  | if length < 3
    then "WARNING: invalid line:\n\($line)" 
    else try ((.[2] | tonumber) as $mag
    | select($mag > 6)
    | $line) catch "WARNING: column 3 is not a recognized number in the line:\n\($line)"
    end )
Output:
The earthquakes from data.txt with a magnitude greater than 6 are:

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
1/25/4567    EdgeCase3           6.1

Julia

Using the example data as a small text file.

using DataFrames, CSV

df = CSV.File("kernighansproblem.txt", delim=" ", ignorerepeated=true,
    header=["Date", "Location", "Magnitude"], types=[DateTime, String, Float64],
    dateformat="mm/dd/yyyy") |> DataFrame

println(filter(row -> row[:Magnitude] > 6, df))
Output:

2×3 DataFrame │ Row │ Date │ Location │ Magnitude │ │ │ DateTime │ String │ Float64 │ ├─────┼─────────────────────┼───────────────┼───────────┤ │ 1 │ 1883-08-27T00:00:00 │ Krakatoa │ 8.8 │ │ 2 │ 1980-05-18T00:00:00 │ MountStHelens │ 7.6 │

Klingphix

arg pop nip len dup

( [get nip]
  [drop drop "data.txt"]
) if

%f 
dup "r" fopen !f
$f 0 < ( [drop "Could not open '" print print "' for reading" print -1 end ] [drop] ) if

[dup split 3 get tonum 6 > ( [drop print nl] [drop drop] ) if]
[$f fgets dup -1 #] 
while

drop
$f fclose

"End " input

Kotlin

// Version 1.2.40

import java.io.File

fun main(args: Array<String>) {
    val r = Regex("""\s+""")
    println("Those earthquakes with a magnitude > 6.0 are:\n")
    File("data.txt").forEachLine {
        if (it.split(r)[2].toDouble() > 6.0) println(it)
    }    
}
Output:

Using the given file:

Those earthquakes with a magnitude > 6.0 are:

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

Lua

For each line, the Lua pattern "%S+$" is used to capture between the final space character and the end of the line.

-- arg[1] is the first argument provided at the command line
for line in io.lines(arg[1] or "data.txt") do  -- use data.txt if arg[1] is nil
  magnitude = line:match("%S+$")
  if tonumber(magnitude) > 6 then print(line) end
end

M2000 Interpreter

Module Find_Magnitude  {
	data$={8/27/1883    Krakatoa            8.8
	5/18/1980    MountStHelens       7.6
	3/13/2009    CostaRica           5.1
	1/23/4567    EdgeCase1           6
	1/24/4567    EdgeCase2           6.0
	1/25/4567    EdgeCase3           6.1
	}
	Open "data.txt" for output as F
	Print #F, data$;
	Close #F
	Open "data.txt" for input as F
	While not eof(#F)
		Line Input #f, part$
		REM if val(mid$(part$,30))>6 then print part$
		if val(mid$(part$,rinstr(rtrim$(part$)," ")))>6 then print part$
	End While
	Close #F
}
Find_Magnitude


Output:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
1/25/4567    EdgeCase3           6.1

Mathematica / Wolfram Language

Import["data.txt", "Table"] // Select[Last /* GreaterThan[6]]

Nim

Here is one way to do that:

import strscans

for line in "data.txt".lines:
  var date, name: string
  var magnitude: float
  if scanf(line, "$+ $s$+ $s$f", date, name, magnitude):
    if magnitude > 6:
      echo line
  # else wrong line: ignore.

Here is another way with less checks:

import strutils

for line in "data.txt".lines:
  let magnitude = line.rsplit(' ', 1)[1]
  if magnitude.parseFloat() > 6:
    echo line
Output:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

Perl

perl -n -e '/(\S+)\s*$/ and $1 > 6 and print' data.txt

Phix

with javascript_semantics
constant filename = "data.txt"
string text = iff(platform()=JS or not file_exists(filename)?"""
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1""" : get_text(filename))
sequence lines = split_any(text,"\r\n")
for i=1 to length(lines) do
    sequence r = scanf(lines[i],"%s %f")
    if length(r)=1 and r[1][2]>6 then
        printf(1,"%s\n",{lines[i]})
    end if
end for
Output:
"8/27/1883    Krakatoa            8.8"
"5/18/1980    MountStHelens       7.6"

Phixmonti

argument tail nip len dup
if
    get nip
else
    drop drop "data.txt"
endif

dup "r" fopen
dup 0 < if drop "Could not open '" print print "' for reading" print -1 quit endif
nip

true
while
    dup fgets
    dup 0 < if
        drop false
    else
        dup split 3 get tonum 6 > if drop print else drop drop endif
        true
    endif
endwhile
fclose

PHP

Parse using PHP's fscanf().

<?php

// make sure filename was specified on command line
if ( ! isset( $argv[1] ) )
    die( 'Data file name required' );

// open file and check for success
if ( ! $fh = fopen( $argv[1], 'r' ) )
    die ( 'Cannot open file: ' . $argv[1] );

while ( list( $date, $loc, $mag ) = fscanf( $fh, "%s %s %f" ) ) {
    if ( $mag > 6 ) {
        printf( "% -12s % -19s %.1f\n", $date, $loc, $mag );
    }
}

fclose( $fh );

Usage: Specify file name on command line. Ex: php eq.php data.txt

Output:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

PicoLisp

(load "@lib/misc.l")

(in "kernighan.txt"
   (until (eof)
      (let (Date (read)  Quake (read)  Mag (read))
     (when (> Mag 6)
        (prinl (align -10 Date) " " (align -15 Quake) " " Mag)))))
(bye)
Output:
$ ./kernighan.l 
8/27/1883  Krakatoa        9
5/18/1980  MountStHelens   8

Prolog

Works with: SWI Prolog

Example command line: swipl kernighans_earthquake.pl earthquake.txt.

:- initialization(main, main).

process_line(Line):-
    split_string(Line, "\s\t", "\s\t", [_, _, Magnitude_string]),
    read_term_from_atom(Magnitude_string, Magnitude, []),
    Magnitude > 6,
    !,
    writef('%w\n', [Line]).
process_line(_).

process_stream(Stream):-
    read_line_to_string(Stream, String),
    String \= end_of_file,
    !,
    process_line(String),
    process_stream(Stream).
process_stream(_).

process_file(File):-
    open(File, read, Stream),
    process_stream(Stream),
    close(Stream).

main([File]):-
    process_file(File),
    !.
main(_):-
    swritef(Message, 'File argument is missing\n', []),
    write(user_error, Message).
Output:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

PureBasic

If OpenConsole() And ReadFile(0,"data.txt")
  PrintN("Those earthquakes with a magnitude > 6.0 are:")  
  While Not Eof(0)    
    buf$=Trim(ReadString(0))    
    If ValF((StringField(buf$,CountString(buf$," ")+1," ")))>6.0
      PrintN(buf$)
    EndIf
  Wend
  CloseFile(0)
  Input()
EndIf
Output:
Those earthquakes with a magnitude > 6.0 are:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

Python

Typed into a bash shell or similar:

python -c '
with open("data.txt") as f:
    for ln in f:
        if float(ln.strip().split()[2]) > 6:
            print(ln.strip())'


Or, if scale permits a file slurp and a parse retained for further processing, we can combine the parse and filter with a concatMap abstraction:

from os.path import expanduser
from functools import (reduce)
from itertools import (chain)


# largeQuakes :: Int -> [String] -> [(String, String, String)]
def largeQuakes(n):
    def quake(threshold):
        def go(x):
            ws = x.split()
            return [tuple(ws)] if threshold < float(ws[2]) else []
        return lambda x: go(x)
    return concatMap(quake(n))


# main :: IO ()
def main():
    print (
        largeQuakes(6)(
            open(expanduser('~/data.txt')).read().splitlines()
        )
    )


# GENERIC ABSTRACTION -------------------------------------

# concatMap :: (a -> [b]) -> [a] -> [b]
def concatMap(f):
    return lambda xs: list(
        chain.from_iterable(
            map(f, xs)
        )
    )


# MAIN ---
if __name__ == '__main__':
    main()
Output:
[('8/27/1883', 'Krakatoa', '8.8'), ('5/18/1980', 'MountStHelens', '7.6')]

Racket

The file specified contains the three lines from the task description.

This is just a file filter, matching lines are printed out.

#lang racket

(with-input-from-file "data/large-earthquake.txt"
  (λ ()
    (for ((s (in-port read-line))
          #:when (> (string->number (third (string-split s))) 6))
    (displayln s))))


Or, defining a list -> list function in terms of filter:

#lang racket

; largeQuakes :: Int -> [String] -> [String]
(define (largeQuakes n xs)
  (filter
   (λ (x)
     (< n (string->number (last (string-split x)))))
   xs))

; main :: IO ()
(module* main #f
  (display
   (unlines
    (largeQuakes
     6
     (lines (readFile "~/quakes.txt"))))))

     
; GENERIC ---------------------------------------------

; lines :: String -> [String]
(define (lines s)
  (string-split s "\n"))

; readFile :: FilePath -> IO String
(define (readFile fp)
  (file->string
   (expand-user-path fp)))

; unlines :: [String] -> String
(define (unlines xs) 
  (string-join xs "\n"))
Output:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

To combine filtering with more pre-processing, we can use concatMap in place of filter:

#lang racket

(require gregor) ; Date parsing

; test :: IO ()
(module* main #f
  (for
      ([q ((quakesAbove 6)
           (lines (readFile "~/quakes.txt")))])
    (writeln q)))


; quakesAbove :: Int -> [String] -> [(Date, String, Float)]
(define (quakesAbove n)
  (λ (xs)
    ((concatMap
      (λ (x)
        (local [(define-values (dte k mgn)
                  (apply values (string-split x)))
                (define m (string->number mgn))]
          (if (< n m)
              (list (list (parse-date dte "M/d/y") k m))
              '()))))
     xs)))
     
; GENERIC ---------------------------------------------

; concatMap :: (a -> [b]) -> [a] -> [b]
(define (concatMap f)
  (λ (xs)
    (foldr (λ (x a) (append (f x) a)) '() xs)))

; lines :: String -> [String]
(define (lines s)
  (string-split s "\n"))

; readFile :: FilePath -> IO String
(define (readFile fp)
  (file->string
   (expand-user-path fp)))
Output:
(#<date 1883-08-27> "Krakatoa" 8.8)
(#<date 1980-05-18> "MountStHelens" 7.6)

Raku

(formerly Perl 6)

Works with: Rakudo version 2018.03

Pass in a file name, or use default for demonstration purposes.

$_ = @*ARGS[0] ?? @*ARGS[0].IO !! q:to/END/;
    8/27/1883    Krakatoa            8.8
    5/18/1980    MountStHelens       7.6
    3/13/2009    CostaRica           5.1
    END

map { .say if .words[2] > 6 }, .lines;

REXX

A little extra coding was added to provide:

  •   an output title   (with centering and better alignment)
  •   an error message for when the input file wasn't found   (or is empty)
  •   the number of records read
  •   the number of records that met the qualifying magnitude
  •   the qualifying magnitude
/*REXX program to read a file containing a list of earthquakes:   date, site, magnitude.*/
parse arg iFID mMag .                            /*obtain optional arguments from the CL*/
if iFID=='' | iFID==","  then iFID= 'earthquakes.dat' /*Not specified?  Then use default*/
if mMag=='' | mMag==","  then mMag= 6                 /* "      "         "   "     "   */
#=0                                              /*# of earthquakes that meet criteria. */
   do j=0  while lines(iFID)\==0                 /*read all lines in the input file.    */
   if j==0  then say 'Reading from file: ' iFID  /*show the name of the file being read.*/
   parse value linein(iFID) with date site mag . /*parse three words from an input line.*/
   if mag<=mMag  then iterate                    /*Is the quake too small?  Then skip it*/
   #= # + 1;     if j==0  then say               /*bump the number of qualifying quakes.*/
   if #==1  then say center('date', 20, "═")     '=magnitude='     center("site", 20, '═')
   say               center(date, 20)      center(mag/1, 11)   '  '        site
   end   /*j*/                                   /*stick a fork in it,  we're all done. */
say
say
if j\==0  then say j  'records read from file: ' iFID
say
if j==0  then say er 'file    '          iFID           "   is empty or not found."
         else say #  ' earthquakes listed whose magnitude is  ≥ ' mMag
output   when using the default inputs:
Reading from file:  earthquakes.dat

════════date════════ =magnitude= ════════site════════
     08/27/1883          8.8        Krakatoa
     05/18/1980          7.6        MountStHelens


3 records read from file:  earthquakes.dat

2  earthquakes listed whose magnitude is  ≥  6

Ring

# Project  : Kernighans large earthquake problem

load "stdlib.ring"
nr = 0 
equake = list(3)
fn = "equake.txt"
fp = fopen(fn,"r")

while not feof(fp)
         nr = nr + 1 
         equake[nr] = readline(fp)
end 
fclose(fp)
for n = 1 to len(equake)
     for m = 1 to len(equake[n])
          if equake[n][m] = " "
             sp = m
          ok
     next
     sptemp = right(equake[n],len(equake[n])-sp)
     sptemo = number(sptemp)
     if sptemp > 6
        see equake[n] + nl
     ok
next

Output:

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens   7.6

Ruby

ruby -nae "$F[2].to_f > 6 && print" data.txt

A more interesting problem. Print only the events whose magnitude is above average.

Contents of the file:

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1
2000-02-02  Foo               7.7
1959-08-08   Bar             6.2
1849-09-09  Pym                9.0

The command:

ruby -e"m=$<.to_a;f=->s{s.split[2].to_f};a=m.reduce(0){|t,s|t+f[s]}/m.size;puts m.select{|s|f[s]>a}" e.txt

Output:

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
2000-02-02  Foo               7.7
1849-09-09  Pym                9.0

Rust

fn main() -> Result<(), Box<dyn std::error::Error>> {
    use std::io::{BufRead, BufReader};

    for line in BufReader::new(std::fs::OpenOptions::new().read(true).open("data.txt")?).lines() {
        let line = line?;

        let magnitude = line
            .split_whitespace()
            .nth(2)
            .and_then(|it| it.parse::<f32>().ok())
            .ok_or_else(|| format!("Could not parse scale: {}", line))?;

        if magnitude > 6.0 {
            println!("{}", line);
        }
    }

    Ok(())
}

Scala

scala.io.Source.fromFile("data.txt").getLines
  .map("\\s+".r.split(_))
  .filter(_(2).toDouble > 6.0)
  .map(_.mkString("\t"))
  .foreach(println)

Snobol

This is hard-coded to read the input from "data.txt".

        input(.quake, 1,, 'data.txt')       :f(err)
        num = '.0123456789'

line    test = quake                        :f(end)
        test span(num) . magnitude rpos(0)  :f(line)
        output = gt(magnitude,6) test       :(line)

err     output = 'Error!'
end
Output:
$ cat data.txt
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1
1/23/4567    EdgeCase1           6
1/24/4567    EdgeCase2           6.0
1/25/4567    EdgeCase3           6.1
$ snobol4 quakes.sno
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
1/25/4567    EdgeCase3           6.1

Swift

Expects the program to be started with the path to the data file.

import Foundation

guard let path = Array(CommandLine.arguments.dropFirst()).first else {
  fatalError()
}

let fileData = FileManager.default.contents(atPath: path)!
let eventData = String(data: fileData, encoding: .utf8)!

for line in eventData.components(separatedBy: "\n") {
  guard let lastSpace = line.lastIndex(of: " "), // Get index of last space
        line.index(after: lastSpace) != line.endIndex, // make sure the last space isn't the end of the line
        let magnitude = Double(String(line[line.index(after: lastSpace)])),
        magnitude > 6 else { // Finally check the magnitude
    continue
  }

  print(line)
}

Tcl

Inspired by awk.

catch {console show}          ;## show console when running from tclwish
catch {wm withdraw .}

set filename "data.txt"
set fh [open $filename]
set NR 0                ;# number-of-record, means linenumber

while {[gets $fh line]>=0} {        ;# gets returns length of line, -1 means eof
    incr NR
    set  line2 [regexp -all -inline {\S+} $line]  ;# reduce multiple whitespace
    set  fld   [split $line2]   ;# split line into fields, at whitespace
    set  f3    [lindex $fld 2]  ;# zero-based
   #set  NF    [llength $fld]       ;# number-of-fields

    if {$f3 > 6} { puts "$line" }
}
close $fh

Visual Basic .NET

Translation of: C#
Imports System.IO

Module Module1

    Function LargeEarthquakes(filename As String, limit As Double) As IEnumerable(Of String())
        Return From line In File.ReadLines(filename)
               Let parts = line.Split(CType(Nothing, Char()), StringSplitOptions.RemoveEmptyEntries)
               Where Double.Parse(parts(2)) > limit
               Select parts
    End Function

    Sub Main()
        For Each earthquake In LargeEarthquakes("data.txt", 6)
            Console.WriteLine(String.Join(" ", earthquake))
        Next
    End Sub

End Module

V (Vlang)

import os
fn main() {
    lines := os.read_lines('data.txt')?
    println('Those earthquakes with a magnitude > 6.0 are:\n')
    for line in lines {
        fields := line.fields()
        mag := fields[2].f64()
        if mag > 6.0 {
            println(line)
        }
    }
}
Output:
Those earthquakes with a magnitude > 6.0 are:

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

Wren

Library: Wren-pattern
import "io" for File
import "os" for Process
import "./pattern" for Pattern

var args = Process.arguments
if (args.count != 1) Fiber.abort("Please pass just the name of the date file.")
var fileName = args[0]
var lines = File.read(fileName).split("\n").map { |l| l.trim() }.where { |l| l != "" }
var p = Pattern.new("+1/s")
System.print("The earthquakes from '%(fileName)' with a magnitude of greater than 6 are:\n")
for (line in lines) {
    var data = p.splitAll(line)
    if (data.count != 3) Fiber.abort("Invalid line : %(line)")
    var mag = Num.fromString(data[2])
    if (mag > 6) System.print(line)
}
Output:
The earthquakes from 'data.txt' with a magnitude of greater than 6 are:

8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6

XPL0

Usage: quake <data.txt

int C;
[loop   [OpenO(8);              \get line from input file
        repeat  C:= ChIn(1);
                ChOut(8, C);    \save it in buffer device 8
                if C = $1A\EOF\ then quit;
        until   C = $0A\LF\;
        OpenI(8);
        repeat until ChIn(8) <= $20\space\;
        repeat until ChIn(8) >  $20\space\;
        repeat until ChIn(8) <= $20\space\;
        if RlIn(8) > 6.0 then
            [OpenI(8);          \output saved line to console
            repeat  C:= ChIn(8);
                    ChOut(0, C);
            until   C = $0A\LF\;
            ];
        ];
]
Output:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
1/25/4567    EdgeCase3           6.1

for data.txt
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6
3/13/2009    CostaRica           5.1
1/23/4567    EdgeCase1           6
1/24/4567    EdgeCase2           6.0
1/25/4567    EdgeCase3           6.1

Yabasic

if peek("argument") then
    filename$ = peek$("argument")
else
    filename$ = "data.txt"
end if

dim tok$(1)
a = open(filename$)
if not a error "Could not open '" + filename$ + "' for reading"
while(not eof(a)) 
  line input #a a$
  void = token(a$, tok$())
  if val(tok$(3)) > 6 print a$
wend
close a

zkl

While lexical comparsions [of numeric data] are fine for this problem, it is bad practice so I don't do it (written so text is automatically converted to float).

fcn equake(data,out=Console){ 
   data.pump(out,fcn(line){ 6.0line.split()[-1] },Void.Filter)
}
equake(Data(Void,
#<<<
"8/27/1883    Krakatoa            8.8\n"
"5/18/1980    MountStHelens       7.6\n"
"3/13/2009    CostaRica           5.1\n"
#<<<
));

or

equake(File("equake.txt"));

or

$ zkl --eval 'File.stdin.pump(Console,fcn(line){ 6.0<line.split()[-1] },Void.Filter)' < equake.txt
Output:
8/27/1883    Krakatoa            8.8
5/18/1980    MountStHelens       7.6