Skip to content

Instantly share code, notes, and snippets.

@armstnp
Last active November 2, 2017 19:40
Show Gist options
  • Save armstnp/63961a54bbdadc855652bd8abe5d66da to your computer and use it in GitHub Desktop.
Save armstnp/63961a54bbdadc855652bd8abe5d66da to your computer and use it in GitHub Desktop.
Advent of Code 2016 - Day 1 in Pharo Smalltalk
Object subclass: #AdventInputFile
instanceVariableNames: 'content'
classVariableNames: ''
poolDictionaries: ''
category: 'AdventOfCode2016'
!
!AdventInputFile methodsFor: 'parsing' stamp: 'NathanArmstrong 10/30/2017 00:01'!
splitBy: separator
"Splits the string content using the given separator, turning it into an array"
content := separator split: content
!
trimmed
"Trims the content string"
content := content trimmed
! !
!AdventInputFile methodsFor: 'accessing' stamp: 'NathanArmstrong 10/30/2017 00:01'!
content
"Returns the content of the file, including any parsing transformations performed"
^ content
! !
!AdventInputFile methodsFor: 'initialization' stamp: 'NathanArmstrong 10/26/2017 01:32'!
initialize
content := nil
! !
!AdventInputFile methodsFor: 'instance creation' stamp: 'NathanArmstrong 10/30/2017 00:01'!
from: path
"Pulls content from the given file path"
content :=
(FileSystem disk readStreamOn: path)
contents
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
AdventInputFile class
instanceVariableNames: ''
!
!AdventInputFile class methodsFor: 'instance creation' stamp: 'NathanArmstrong 10/29/2017 23:56'!
from: path
"Create a instance containing content from the given path"
^ self new from: path
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
AdventInputFile subclass: #Day1Input
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'AdventOfCode2016'
!
!Day1Input methodsFor: 'parsing' stamp: 'NathanArmstrong 10/30/2017 00:01'!
parse
"Creates a sequence of instructions for the Day 1 problem from this file's contents."
(content isKindOf: HqPathSequence)
ifFalse: [ content := HqPathSequence from: content ]
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
Day1Input class
instanceVariableNames: ''
!
!Day1Input class methodsFor: 'instance creation' stamp: 'NathanArmstrong 11/2/2017 00:56'!
from: path
^ (self new from: path)
trimmed;
splitBy: ', ';
parse
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
Object subclass: #HqPathInstruction
instanceVariableNames: 'direction steps'
classVariableNames: ''
poolDictionaries: ''
category: 'AdventOfCode2016'
!
!HqPathInstruction methodsFor: 'initialization' stamp: 'NathanArmstrong 10/30/2017 00:01'!
initialize
direction := nil.
steps := nil
!
from: string
"sets the path direction and step count from strings such as L12 or R5"
direction := string first = $L ifTrue: [ #left ] ifFalse: [ #right ].
steps := (string trimLeft: [ :c | (c = $L) | (c = $R) ]) asNumber
! !
!HqPathInstruction methodsFor: 'applying' stamp: 'NathanArmstrong 10/30/2017 00:01'!
apply: pather
"Applies this instruction to the given pather, turning and moving it as defined."
direction = #left ifTrue: [ pather turnLeft ] ifFalse: [ pather turnRight ].
pather step: steps
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
HqPathInstruction class
instanceVariableNames: ''
!
!HqPathInstruction class methodsFor: 'instance creation' stamp: 'NathanArmstrong 10/30/2017 00:01'!
from: string
^ self new from: string
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
Object subclass: #HqPathSequence
instanceVariableNames: 'sequence'
classVariableNames: ''
poolDictionaries: ''
category: 'AdventOfCode2016'
!
!HqPathSequence methodsFor: 'initialization' stamp: 'NathanArmstrong 11/2/2017 00:47'!
initialize
sequence := LinkedList new
!
from: seq
"sets the sequence contents from the given collection of instruction strings"
sequence := seq collect: [ :e | HqPathInstruction from: e ]
! !
!HqPathSequence methodsFor: 'applying' stamp: 'NathanArmstrong 11/2/2017 00:47'!
apply: pather
"applies each instruction in this sequence to the given pather in turn"
sequence do: [ :e | e apply: pather ]
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
HqPathSequence class
instanceVariableNames: ''
!
!HqPathSequence class methodsFor: 'instance creation' stamp: 'NathanArmstrong 11/2/2017 00:52'!
from: sequence
^ self new from: sequence
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
Object subclass: #HqPather
instanceVariableNames: 'position direction'
classVariableNames: ''
poolDictionaries: ''
category: 'AdventOfCode2016'
!
!HqPather methodsFor: 'moving' stamp: 'NathanArmstrong 11/2/2017 00:52'!
step: steps
"Take the given number of steps in the current direction"
position := direction * steps + position
! !
!HqPather methodsFor: 'accessing' stamp: 'NathanArmstrong 11/2/2017 00:52'!
blockDistance
"The distance in blocks of the current position from the origin"
| absPos |
absPos := position abs.
^ absPos x + absPos y
!
position: point
"places the pather at the given position"
position := point
! !
!HqPather methodsFor: 'turning' stamp: 'NathanArmstrong 11/2/2017 00:52'!
turnLeft
"Turn 90 degrees counter-clockwise"
direction := direction leftRotated
!
turnRight
"Turn 90 degrees clockwise"
direction := direction rightRotated
! !
!HqPather methodsFor: 'initialization' stamp: 'NathanArmstrong 11/2/2017 00:52'!
initialize
"places the pather at the origin, facing north"
direction := 0@(-1).
position := 0@0
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
HqPather subclass: #HqLoopbackPather
instanceVariableNames: 'visited revisited'
classVariableNames: ''
poolDictionaries: ''
category: 'AdventOfCode2016'
!
!HqLoopbackPather methodsFor: 'initialization' stamp: 'NathanArmstrong 11/2/2017 01:21'!
initialize
super initialize.
visited := Set new.
revisited := LinkedList new
! !
!HqLoopbackPather methodsFor: 'recording' stamp: 'NathanArmstrong 11/2/2017 01:21'!
recordPosition
"records the current position as having been visited, and also as revisited if it has previously passed through this point"
(visited includes: position) ifTrue: [ revisited add: position ].
visited add: position
! !
!HqLoopbackPather methodsFor: 'moving' stamp: 'NathanArmstrong 11/2/2017 01:21'!
returnToFirstRevisited
"Returns the pather to the first point it revisited, or does nothing if it has revisited no points."
revisited isEmpty
ifFalse: [ self position: revisited first ]
!
step: steps
"Take the given number of steps in the current direction, recording each unit-aligned point visited along that route."
steps timesRepeat: [
super step: 1.
self recordPosition
]
! !
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment