Skip to content

Instantly share code, notes, and snippets.

@Hendekagon
Last active May 1, 2017 17:01
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save Hendekagon/1c357aafa7b8ea1ff335ce148d8443ba to your computer and use it in GitHub Desktop.
Save Hendekagon/1c357aafa7b8ea1ff335ce148d8443ba to your computer and use it in GitHub Desktop.
bit pattern symmetry layout for Roassal
pointFor: bits
"
Returns a point x@y for the given list of bits,
where x is given by the symmetry of the bit pattern - symmetrical patterns go to the centre,
symmetry on the left half goes to the centre of the left half etc,
and y is proportional to the number of 1s, so 000000 is at the top centre and 111111 is at the bottom centre,
1000 is at the left, 0001 is at the right etc.
use an RTGraphBuilder and a RTLayout subclass FnLayout that does:
doExecute: elements
elements do:[:element |
translator translateTopLeftOf: element
to: (fn value: element model).
].
self step.
then b layout use: (FnLayout new on:[:e | ((F pointFor: (e last)) scaleBy: 2@600)]).
F pointFor: #(1 0 1).
"
| |
^ (bits isEmpty)
ifTrue: [0@0]
ifFalse:[
((bits size) = 1)
ifTrue:[0@(1.5 * (bits at: 1))]
ifFalse:[
((bits at: 1) = 1)
ifTrue:[((bits at: (bits size)) = 1)
ifTrue:[0@5 + (F pointFor: (bits allButFirst allButLast))]
ifFalse:[(-2.5 * (2 raisedTo: bits size))@2 + (F pointFor: (bits allButFirst))]
]
ifFalse:[((bits at: (bits size)) = 1)
ifTrue:[(2.5 * (2 raisedTo: bits size))@2 + (F pointFor: (bits allButLast))]
ifFalse:[0@(3.5 / (bits size)) + (F pointFor: (bits allButFirst allButLast))]
].
]].
'From Pharo3.0 of 18 March 2013 [Latest update: #30846] on 1 May 2017 at 5:58:40.759228 pm'!
Object subclass: #F
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'fredkin'!
!F commentStamp: 'mjc 3/26/2015 10:19' prior: 0!
bits
!
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
F class
instanceVariableNames: ''!
!F class commentStamp: '<historical>' prior: 0!
!
!F class methodsFor: 'as yet unclassified' stamp: 'mjc 5/1/2017 17:00'!
pointFor: bits
"
Returns a point x@y for the given list of bits e.g. #(1 0 1 1),
where x is weighted by the symmetry of the bit pattern
and y is proportional to the number of 1s
F pointFor: #(1 0 1).
"
| |
^ (bits isEmpty)
ifTrue: [0@0]
ifFalse:[
((bits size) = 1)
ifTrue:[0@(1.5 * (bits at: 1))]
ifFalse:[
((bits at: 1) = 1)
ifTrue:[((bits at: (bits size)) = 1)
ifTrue:[0@5 + (F pointFor: (bits allButFirst allButLast))]
ifFalse:[(-2.5 * (2 raisedTo: bits size))@2 + (F pointFor: (bits allButFirst))]
]
ifFalse:[((bits at: (bits size)) = 1)
ifTrue:[(2.5 * (2 raisedTo: bits size))@2 + (F pointFor: (bits allButLast))]
ifFalse:[0@(3.5 / (bits size)) + (F pointFor: (bits allButFirst allButLast))]
].
]].! !
!F class methodsFor: 'as yet unclassified' stamp: 'mjc 6/14/2014 19:19'!
bitsToInt: bits
^ (bits
with: (((bits size - 1) to: 0 by: -1) collect:[:x | 2 raisedTo: x])
collect:[:bit :power | bit * power])
reduce:[:x :y | x + y].! !
!F class methodsFor: 'as yet unclassified' stamp: 'mjc 5/1/2017 17:53'!
addKeys: b
" b is a RTGraphBuilder "
| k |
k := Dictionary new.
k at: $z put: [:e | b view canvas camera scale: (b view canvas camera scale) * 0.9;
translateTo:(e position * b view canvas camera scale).].
k at: $x put: [:e | b view canvas camera scale: (b view canvas camera scale) * 1.1;
translateTo:(e position * b view canvas camera scale).].
k at: $c put: [:e | b view canvas camera focusOnCenter].
"k at: $q put: [:e | (b layouts at:1) layout scale: 0.5@1].
k at: $w put: [:e | (b layouts at:1) layout scale: 2@1]."
k at: $a put: [:e | b view elements do:[:s | s trachelShape scaleBy: 0.5]].
k at: $s put: [:e | b view elements do:[:s | s trachelShape scaleBy: 2]].
b view
on: TRKeyDown
do: [:e |
k at: e keyValue asCharacter ifPresent:[:a | a value:e].
b view signalUpdate.
].
^ b.! !
!F class methodsFor: 'as yet unclassified' stamp: 'mjc 6/13/2014 18:02'!
bits: i length: n
| b s |
b := i asBits.
s := WriteStream on: OrderedCollection new.
(n - b size) timesRepeat:[s nextPut: 0].
s nextPutAll: b.
^ s contents.
! !
!F class methodsFor: 'as yet unclassified' stamp: 'mjc 5/1/2017 13:02'!
graycode: n
"Returns the n-bit gray code. F graycode: 3."
^(n == 1)
ifTrue:[OrderedCollection with: (OrderedCollection with: 0) with: (OrderedCollection with: 1)]
ifFalse:[
| g b |
g := F graycode: n - 1.
b := (g collect:[:l | l copy addFirst: 0; yourself])
addAll: (g reversed collect:[:l | l copy addFirst: 1; yourself]);
yourself.
].! !
!F class methodsFor: 'as yet unclassified' stamp: 'mjc 5/1/2017 17:57'!
bitsGraph: n
"Returns a graph of binary numbers plotted by their symmetry"
| b nodes |
nodes := (F graycode: n) withIndexCollect:[:i :j | {j . i}].
b := RTGraphBuilder new.
F addKeys: b.
b nodes color: Color black.
b edges
connectFrom: #yourself;
color: (Color blue).
b edges
connectTo: [:x | nodes at: (((x first) + 1) min: nodes size)];
useInLayout.
b layout use: (FnLayout new on:[:e | ((F pointFor: (e last)) scaleBy: 2@600)]).
b addAll: nodes.
b open.
^ b.! !
'From Pharo3.0 of 18 March 2013 [Latest update: #30846] on 1 May 2017 at 5:58:42.358243 pm'!
RTLayout subclass: #FnLayout
instanceVariableNames: 'fn'
classVariableNames: ''
poolDictionaries: ''
category: 'fredkin'!
!FnLayout commentStamp: 'mjc 3/27/2015 11:54' prior: 0!
Layout with a block
!
!FnLayout methodsFor: 'as yet unclassified' stamp: 'mjc 5/1/2017 16:18'!
doExecute: elements
elements do:[:element |
translator translateTopLeftOf: element
to: (fn value: element model).
].
self step.! !
!FnLayout methodsFor: 'as yet unclassified' stamp: 'mjc 5/1/2017 17:54'!
on: aBlock
fn := aBlock.
! !
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment