Time formatting (HH:MM:SS) in any Smalltalk dialect - string

I have three integer values, say
h := 3.
m := 19.
s := 8.
I would like to produce the string '03:19:08'. I know how to turn a number into a string, and even pad it with a zero if necessary. So as a first pass I wrote this absolutely horrific code:
h < 10 ifTrue: [hs := '0', (h asString)] ifFalse: [hs := h asString].
m < 10 ifTrue: [ms := '0', (m asString)] ifFalse: [ms := m asString].
s < 10 ifTrue: [ss := '0', (s asString)] ifFalse: [ss := s asString].
Transcript show: hs, ':', ms, ':', ss.
Transcript nl.
Now obviously I need to clean this up and so was wondering, among other things what the most idiomatic Smalltalk approach would be here. Could it be something like (not legal Smalltalk obviously):
aCollectionWithHMS each [c | padWithZero] join ':'
I found a discussion on streams with a print method taking a separatedBy argument but wouldn't there be a simpler way to do things just with strings?
Or perhaps there is a more elegant way to pad the three components and then I could just return hs, ':', ms, ':', ss ?
Or, is there an interface to POSIX time formatting (or something similar) common to all Smalltalks? I know GNU Smalltalk can link to C but this is way too much overkill for this simple problem IMHO.
EDIT
I got a little closer:
z := {h . m . s} collect: [:c | c < 10 ifTrue: ['0', c asString] ifFalse: [c asString]].
(Transcript show: ((z at: 1), ':', (z at: 2), ':', (z at: 3))) nl.
But the direct access of collection elements makes me sad. I found a page documenting the joining method asStringWith but that method is unsupported, it seems in GNU Smalltalk.

Here is a way to do this in Pharo:
String streamContents: [:stream |
{h.m.s}
do: [:token | token printOn: stream base: 10 nDigits: 2]
separatedBy: [stream nextPut: $:]]
Explanation:
The streamContents: message answers with the contents of the WriteStream represented by the formal block argument stream.
The do:separatedBy: message enumerates the tokens h, m and s evaluating the do: block for each of them and inserting the evaluation of the second block between consecutive tokens.
The printOn:base:nDigits: message dumps on the stream the base 10 representation of the token padded to 2 digits.
If the dialect you are using doesn't have the printOn:base:nDigits: method (or any appropriate variation of it), you can do the following:
String streamContents: [:stream |
{h.m.s}
do: [:token |
token < 10 ifTrue: [stream nextPut: $0].
stream nextPutAll: token asString]
separatedBy: [stream nextPut: $:]]
Finally, if you think you will be using this a lot, I would recommend adding the message hhmmss to Time (instance side), implemented as above with self hours instead of h, etc. Then it would be a matter of sending
(Time hour: h minute: m second: s) hhmmss
assuming you have these three quantities instead of a Time object, which would be unusual. Otherwise, you would only need something like
aTime hhmmss
ADDENDUM
Here is another way that will work on any dialect:
{h.m.s}
inject: ''
into: [:r :t | | pad colon |
pad := t < 10 ifTrue: ['0'] ifFalse: [''].
colon := r isEmpty ifTrue: [''] ifFalse: [':'].
r , colon, pad, t asString]
The inject:into: method builds its result from the inject: argument (the empty String in this case) and keeps replacing the formal block argument r with the value of the previous iteration. The second formal argument t is replaced with the corresponding element of each iteration.
ADDENDUM 2
time := '00:00:00' copy.
{h asString. m asString. s asString} withIndexDo: [:t :i |
time at: i - 1 * 3 + 2 put: t last.
t size = 2 ifTrue: [time at: i - 1 * 3 + 1 put: t first]].
^time
The copy is necessary to make sure that the literal is not modified.

Related

Replacing substring in second occurrence in prolog

First of all, this is not a homework. I'm studying Computer Sciences in my home, to learn a little more alone.
I'm doing an excercise. It says like this:
Construct a predicate called replaceAtomsString/4 so that given
a string s as the first parameter, a number N as the second parameter,
and a pair of atoms [g, h] (list) as the third parameter, unify in a
fourth parameter the replacement in the Nth apparition of g in s
replacing it by h. Example:
replaceAtomsString (sAbbbsAbbasA, 2, [sA, cc], X) should result in
X = sAbbbccbbasA
So, my first approach was trying to build a list with the string, just like prolog do with every string. After all, i've built this code:
substitute(X, S, T, Y) :-
append(S, Xt, X), % i.e. S is the first part of X, the rest is Xt
!,
substitute(Xt, S, T, Yt),
append(T, Yt, Y).
substitute([Xh|Xt], S, T, [Xh|Yt]) :-
substitute(Xt, S, T, Yt).
But it returns false on every attempt.
Any ideas?
Since you need substantial work to get your code done, here is how to perform the task using the available libraries.
sub_atom/5 it's a rather powerful predicate to handle atoms. Coupled with call_nth/2, the solution is straightforward and more general than what would result coding the loop around N.
replaceAtomsString(S,N,[G,H],X) :-
call_nth(sub_atom(S,Before,_,After,G),N),
sub_atom(S,0,Before,_,Left),
sub_atom(S,_,After,0,Right),
atomic_list_concat([Left,H,Right],X).
Example running your query, but leaving N to be computed:
?- replaceAtomsString(sAbbbsAbbasA, N, [sA, cc], X).
N = 1,
X = ccbbbsAbbasA ;
N = 2,
X = sAbbbccbbasA ;
N = 3,
X = sAbbbsAbbacc ;
false.

Indices of a substring in Smalltalk

It seems Smalltalk implementations misses an algorithm which return all the indices of a substring in a String. The most similar ones returns only one index of an element, for example : firstIndexesOf:in: , findSubstring:, findAnySubstring: variants.
There are implementations in Ruby but the first one relies on a Ruby hack, the second one does not work ignoring overlapping Strings and the last one uses an Enumerator class which I don't know how to translate to Smalltalk. I wonder if this Python implementation is the best path to start since considers both cases, overlapping or not and does not uses regular expressions.
My goal is to find a package or method which provides the following behavior:
'ABDCDEFBDAC' indicesOf: 'BD'. "#(2 8)"
When overlapping is considered:
'nnnn' indicesOf: 'nn' overlapping: true. "#(0 2)"
When overlapping is not considered:
'nnnn' indicesOf 'nn' overlapping: false. "#(0 1 2)"
In Pharo, when a text is selected in a Playground, a scanner detects the substring and highlights matches. However I couldn't find a String implementation of this.
My best effort so far results in this implementation in String (Pharo 6):
indicesOfSubstring: subString
| indices i |
indices := OrderedCollection new: self size.
i := 0.
[ (i := self findString: subString startingAt: i + 1) > 0 ] whileTrue: [
indices addLast: i ].
^ indices
Let me firstly clarify that Smalltalk collections are 1-based, not 0-based. Therefore your examples should read
'nnnn' indexesOf: 'nn' overlapping: false. "#(1 3)"
'nnnn' indexesOf: 'nn' overlapping: true. "#(1 2 3)"
Note that I've also taken notice of #lurker's observation (and have tweaked the selector too).
Now, starting from your code I would change it as follows:
indexesOfSubstring: subString overlapping: aBoolean
| n indexes i |
n := subString size.
indexes := OrderedCollection new. "removed the size"
i := 1. "1-based"
[
i := self findString: subString startingAt: i. "split condition"
i > 0]
whileTrue: [
indexes add: i. "add: = addLast:"
i := aBoolean ifTrue: [i + 1] ifFalse: [i + n]]. "new!"
^indexes
Make sure you write some few unit tests (and don't forget to exercise the border cases!)
Edited
It would also be nice if you would tell us what you need to achieve in the "greater picture". Sometimes Smalltalk offers different approaches.
Leandro beat me to the the code (and his code is more efficient), but I have already written it so I'll share it too. Heed his advice on Smalltalk being 1-based => rewritten example.
I have used Smalltalk/X and Pharo 6.1 for the example.
The code would be:
indexesOfSubstring: substringToFind overlapping: aBoolean
| substringPositions aPosition currentPosition |
substringPositions := OrderedSet new. "with overlap on you could get multiple same
positions in the result when there is more to find in the source string"
substringToFindSize := substringToFind size. "speed up for large strings"
aPosition := 1.
[ self size > aPosition ] whileTrue: [
currentPosition := self findString: substringToFind startingAt: aPosition.
(currentPosition = 0) ifTrue: [ aPosition := self size + 1 ] "ends the loop substringToFind is not found"
ifFalse: [
substringPositions add: currentPosition.
aBoolean ifTrue: [ aPosition := aPosition + 1 ] "overlapping is on"
ifFalse: [ aPosition := currentPosition + substringToFindSize ] "overlapping is off"
]
].
^ substringPositions
I have fixed some issues that occured to me. Don't forget to test it as much as you can!

Understanding MCPL function call

Analyzing a solution to the eight queens puzzle using bitwise operations written by Martin Richards, I'm having a hard time understanding basic MCPL function syntax, despite consulting the language manual.
Given below is the full program:
GET "mcpl.h"
STATIC count, all
FUN try
: ?, =all, ? => count++
: ld, cols, rd => LET poss = ~(ld | cols | rd) & all
WHILE poss DO
{ LET bit = poss & -poss
poss -:= bit
try( (ld|bit)<<1, cols|bit, (rd|bit)>>1 )
}
FUN start : =>
all := 1
FOR n = 1 TO 12 DO
{ count := 0
try(0, 0, 0)
writef("There are %5d solutions to %2d-queens problem\n", count, n)
all := 2*all + 1
}
RETURN 0
What I fail to understand is the first two lines of the function try, namely, the question mark ? syntax and how parameters are passed (and handled).
The manual reads that
A question mark (?) may be used as a constant with undefined value.
as well as
Patterns are used in function definitions. [...] A question mark (?) or empty pattern will match any argument value.
What does this syntax mean for the parameters and how are ld, cols and rd given their initial values?
After finding a paper that further discusses the above and other similar algorithms, I came to find that
: ?, =all, ? => count++
essentially checks if cols == all and if so, a complete solution has been found (increase count).
ld, cols and rd are given parameter values.
What still looks odd to me is the check being executed before the parameters are used, so I might still be missing some details.

Why does map-each preserve the last value for references to the word to set?

map-each can be used to evaluate some code for every member in a collection, and aggregate the results of the evaluation in a block:
>> values: map-each x [1 2] [
print ["Doing mapping for" x]
x * 10
]
Doing mapping for 1
Doing mapping for 2
== [10 20]
I was building a block of blocks in this way. But I forgot that since blocks aren't evaluated by default, the x would be left as-is and not get the value I wanted:
>> blocks: map-each x [1 2] [
print ["Doing mapping for" x]
[x * 10]
]
Doing mapping for 1
Doing mapping for 2
== [[x * 10] [x * 10]]
No surprise there. After the evaluation x has no value--much less the ability to take on many values:
>> probe x
** Script error: x has no value
So it's too late, the evaluation must be done with a REDUCE or COMPOSE inside the body of the map-each. But...
>> reduce first blocks
== [20]
>> reduce second blocks
== [20]
The evaluations of items in the result block don't throw an error, but behave as if x had the value of the last iteration.
How is it doing this? Should it be doing this?
Just like 'FOREACH, 'MAP-EACH binds the block you give it within a context it creates and executes it there.
the X is never created globally. the fact that you gave it a word (and not a lit-word) as an argument is managed by the function's interface which probably uses the lit-word notation, and uses the word given, as-is, un-evaluated, instead of the value it may contain.
for this reason, the X used in your call to map-each doesn't trigger a
** Script error: x has no value
since map-each is grabbing it before it gets evaluated and only uses the word as a token, directly.
To illustrate how binding works more vividly and to show how 'X may survive existence past its original context, here is an example which illustrates the foundation of how words are bound in Rebol (and the fact that this binding persists).
look at this example:
a: context [x: "this"]
b: context [x: "is"]
c: context [x: "sensational!"]
>> blk: reduce [in a 'x in b 'x in c 'x]
== [x x x]
x: "doh!"
== "doh!"
>> probe reduce blk
["this" "is" "sensational!"]
We created a single block with three 'X words, but none of them are bound to the same context.
Because the binding in Rebol is static, and scope doesn't exist, the same word can have different values, even when they are being manipulated in the same context (in this case the console is the global | user context).
This is the penultimate example of why a word is really NOT a variable in Rebol.
blocks: map-each x [1 2] [
print ["Doing mapping for" x]
[x * 10]
]
probe bound? first blocks/1
gives this
Doing mapping for 1
Doing mapping for 2
make object! [
x: 2
]

Prolog importing facts from a formatted text file

I have the following input in a text file input.txt
atom1,atom2,atom3
relation(atom1 ,[10,5,2])
relation(atom2 ,[3,10,2])
relation(atom3 ,[6,5,10])
First line includes the list of atoms used in relation predicates in the file and each remaining line represents a relation predicate in order of the first line list.relation(atom1, [x,y,z]) means atom1 has a relation value of 10 with first atom, 5 with the second and 2 with the third
I need to read this file and add represent relation values for each atom seperately.For example , these are the relation values which will be added for atom1 :
assert(relation(atom1, atom1,10)).
assert(relation(atom1, atom2, 5)).
assert(relation(atom1, atom3, 2)).
I have read some prolog io tutorials and seen some recommendations on using DCG but I'm a beginner prolog programmer and having trouble to choose the method for the solving problem. So I'm here to ask help from experienced prolog programmers.
Since you didn't stated what Prolog you're using, here is a snippet written in SWI-Prolog. I attempted to signal non ISO builtins by means of SWI-Prolog docs reference.
parse_input :-
open('input.txt', read, S),
parse_line(S, atoms(Atoms)),
repeat,
( parse_line(S, a_struct(relation(A, L)))
-> store(Atoms, A, L), fail
; true ),
close(S).
:- meta_predicate(parse_line(+, //)).
parse_line(S, Grammar) :-
% see http://www.swi-prolog.org/pldoc/doc_for?object=read_line_to_codes/2
read_line_to_codes(S, L),
L \= end_of_file,
phrase(Grammar, L).
% match any sequence
% note - clauses order is mandatory
star([]) --> [].
star([C|Cs]) --> [C], star(Cs).
% --- DCGs ---
% comma sep atoms
atoms(R) -->
star(S),
( ",",
{atom_codes(A, S), R = [A|As]},
atoms(As)
; {atom_codes(A, S), R = [A]}
).
% parse a struct X,
% but it's far easier to use a builtin :)
% see http://www.swi-prolog.org/pldoc/doc_for?object=atom_to_term/3
a_struct(X, Cs, []) :-
atom_codes(A, Cs),
atom_to_term(A, X, []).
% storage handler
:- dynamic(relation/3).
store(Atoms, A, L) :-
nth1(I, L, W),
nth1(I, Atoms, B),
assertz(relation(A, B, W)).
with the sample input.txt, I get
?- parse_input.
true .
?- listing(relation).
:- dynamic relation/3.
relation(atom1, atom1, 10).
relation(atom1, atom2, 5).
relation(atom1, atom3, 2).
relation(atom2, atom1, 3).
relation(atom2, atom2, 10).
relation(atom2, atom3, 2).
relation(atom3, atom1, 6).
relation(atom3, atom2, 5).
relation(atom3, atom3, 10).
HTH

Resources