Assertions no Pharo Smalltalk

Introdução

Require, ensure e invariant

Bertrand Meyer introduziu Design By Contract em seu livro Object-Oriented Software Construction, sobre Engenharia de Software, exemplificado na sua linguagem e ambiente de programação Eiffel. As assertivas que implementaremos serão requireensure e invariant. A assertiva em require deverá ser satisfeita antes da execução do método ao qual ela se aplica e representa uma pré-condição. A assertiva em ensure deverá ser satisfeita após a execução do método, é uma pós-condição. A assertiva em invariant deve ser verdadeira antes e depois da execução do método.

As assertivas tanto podem ser inseridas manualmente como através de instrumentação.

Assertions

O “framework” Assertions é uma tentativa simples de incorporar Design By Contract de forma manual (sem instrumentação usando meta-programação) nos meus projetos. Ele não vai muito além do que você poderia fazer com a mensagem assert:. Acrescenta um controle do nível de assertivas aplicadas e documenta através de nomes mais especializados o que cada assertiva representa.

Numa segunda etapa foi introduzida a instrumentação que permite o uso de pragmas em vez da inserção manual de assertivas. Os pragmas definem as assertivas que serão inseridas por meta-programação.

Require

O exemplo abaixo ilustra o uso da assertiva require:.

    | answer |
    answer := 666.
    self require: [ answer = 42 ] 

O código acima lança o erro RequireViolation.

Require é usado como pré-condição. Veja o exemplo:

Account>>withdraw: anAmount

    self require: [ anAmount > 0 ].
    
    balance := balance - anAmount

Ensure

Ensure representa uma pós-condição.

    | answer |
    answer := 666.
    
    self ensure: [ answer = 42 ]

O código acima lança o erro EnsureViolation.

Veja um exemplo de uso:

Account>>withdraw: anAmount

    self require: [ anAmount > 0 ].
    
    old_balance := balance.
    
    balance := balance - anAmount.
    
    self ensure: [ balance = (old_balance - anAmount) ]

Invariant

Um invariant deve ser respeitado antes e depois do código.

    | answer |
    answer := 42.
    self invariant: [ answer = 42 ] for: [  
            answer := 666   
    ]

O exemplo abaixo ilustra melhor o seu uso:

Account>>withdraw: anAmount

    self require: [ anAmount > 0 ].
    
    old_balance := balance.
    
    self invariant: [ balance >= 0 ] for: [
    
        balance := balance - anAmount
    
    ].
    
    self ensure: [ balance = (old_balance - anAmount) ]

Os invariantes de classe são, comparados com os requires e ensures, as assertivas que seriam melhor aplicadas com uma instrumentação pois manualmente teriam que ser replicados em todos os métodos, exceto para os getters.

Only after invariant

A mensagem invariant:for: não é adequada para ser usada no método initialize. Os invariantes só podem começar a ser aplicados após toda a configuração que acontece durante a criação de um objeto. No método initialize a mensagem onlyAfterInvariant:for: é a adequada:

Account>>initialize
    self onlyAfterInvariant: [ balance >= 0 ] for: [
        balance := 0.
    ]

Vários invariantes envolvendo o código

    | answer |
    answer := 42.
    
    self invariants: {  
        [ answer isNotNil ].
        [ answer = 42 ].
    } 
    for: [  
        answer := 666
    ]

No exemplo acima as assertivas do invariante são aplicadas antes e depois da execução do código.

É importante que o array passado no primeiro parâmetro seja composto de blocos.

Assertion levels

As assertivas podem ser configuradas para os seguintes níveis:

  • none: nenhuma assertiva estará ativa.
  • require: somente as assertivas require podem lançar erros.
  • ensure: as assertivas require e ensure estão ativas.
  • invariant: os invariantes estão habilitados e também require e ensure
  • all: todos os casos anteriores estão habilitados. Equivale ao nível invariant.

Várias mensagens estabelecem os níveis em uso.

  • beRequireLevel
  • beEnsureLevel
  • beInvariantLevel
  • off
  • on que equivale a beRequireLevel (o nível default)
  • all

As mensagens acima podem ser enviadas à classe Assertions. O exemplo abaixo ilustra isso:

testInvariantBefore
    | answer |
    answer := 666.
    Assertions beInvariantLevel.
    self should: [
        self invariant: [ answer = 42 ] for: [  
            answer := 42    
        ]
    ] 
    raise: BeforeInvariantViolation 

Instrumentação

A instrumentação foi implementada de forma simples alterando o código fonte para inserir as assertions e recompilando-o. O que vai em cada método é especificado com anotações (pragmas) nos métodos a serem instrumentados.

Instrumenter

A classe Instrumenter é uma subclasse de Assertions e possui a capacidade de instrumentar, guiada pelos pragmas, métodos individuais, toda uma classe e todo um pacote (considerado com as tags).

Abaixo segue a lista de métodos de Instrumenter usados na instrumentação:

  • instrumentMethod: aCompiledMethod
  • instrumentInitializeMethodOfClass: aClass
  • instrumentClass: aClass
  • instrumentPackage: aCategory

instrumentMethod:

Instrumenta determinado método. Não serve para instrumentação do método initialize.

instrumentInitializeMethodOfClass:

Instrumenta o método initialize de uma determinada classe.

instrumentClass:

Instrumenta todos os métodos de uma determinada classe.

instrumentPackage:

Instrumenta todas as classes de um determinado pacote. Se for especificada uma tag só instrumenta as classes desta tag.

Exemplo:

Assertions instrumenter instrumentPackage: 'Assertions-Examples'

Somente as classes em Assertions-Examples e em Assertions-Examples-XXX serão instrumentadas.

Níveis de instrumentação

Os níveis de instrumentação são os mesmos que são usados ao inserir assertivas manualmente, mas semânticamente diferentes. Repetimos abaixo:

  • none: nenhuma assertiva será inserida.
  • require: somente as assertivas require serão inseridas.
  • ensure: as assertivas require e ensure serão inseridas.
  • invariant: os invariantes serão inseridos e também o serão require e ensure
  • all: todos os as assertivas serão inseridas. Equivale ao nível invariant.

O nível de instrumentação é independente do nível das assertivas. O nível das assertivas default para a instrumentação é all (todas habilitadas). O nível de instrumentação default é require (neste nível somente as assertivas require são inseridas).

Por exemplo: Podemos instrumentar no nível ensure e habilitar as assertivas no nível require. Como abaixo:

   Assertions beRequireLevel. "Nível para as assertivas".
   Assertions instrumenter beEnsureLevel. "Nível de instrumentação"

No exemplo acima serão inseridas no código as assertivas require e ensure, de acordo com os pragmas. No entanto somente as assertivas require estão habilitadas para lançar erros.

Desta forma você pode ajustar a habilitação das assertivas em lugar de gerar novamente as instrumentação. As vantagens de usar a instrumentação é que pode removê-la do código em produção e voltar a inserí-la no desenvolvimento e na depuração. A colocação de assertivas de forma manual inclui uma maior carga de gerenciamento manual. A instrumentação e posterior remoção também remove o possível impacto no desempenho. Usar assertivas anotadas com pragmas e remover a instrumentação na produção também implica em uma nova atitude em relação a evitar “programação defensiva” em prol de usar a ideia do “Design By Contract”.

Removendo a instrumentação de um método

aClass := BankAccount.
aSelector := #deposit:.
aCompiledMethod := aClass>>aSelector.
Assertions instrumenter restoreMethod: aCompiledMethod

A mensagem restoreMethod: restaura o método à sua versão anterior, sem a instrumentação.

Removendo a instrumentação de uma classe

aClass := BankAccount.
Assertions instrumenter restoreClass: BankAccount

A mensagem restoreClass: restaura os métodos de uma classe às suas versões anteriores, sem a instrumentação.

Removendo a instrumentação de um pacote

aPackage := 'Bank-Core'.
Assertions instrumenter restorePackage: aPackage

A mensagem restorePackage: restaura as classes de um pacote às suas versões anteriores, sem a instrumentação.

No exemplo acima as classes do pacote Bank com a tag Core serão restauradas. Serão restauradas também as classes em Bank-Core-XXX. Por exemplo, se houver classes em Bank-Core-Support elas serão restauradas também.

Edição de métodos instrumentados

Nos métodos instrumentados é inserido o pragma <instrumented>. No caso de se editar um método instrumentado para remover um bug deve-se lembrar que a edição será perdida quando o método for retaurado ao seu estado anterior sem a instrumentação. Uma forma de se evitar isto é remover manualmente o pragma <instrumented>. As instrumentações inseridas no meio do código podem ser removidas manualmente quando se achar que não se precisa mais delas para confinar o bug. Obviamente não se deve remover os pragmas requireensure e invariant que servirão para guiar instrumentações futuras.

Exemplo de instrumentação

Abaixo mostramos um exemplo de instrumentação baseado num do “testes” criados.

Antes da instrumentação

initialize 
    <invariant: 'z = 42'>
    super initialize. 
    z := 42'

Os pragmas invariant:, que valem para toda a classe, são inseridos no método initialize.

methodWithAssertions: x
    <require: 'x > 0'>
    <ensure: 'y = (x + 1)'>
    | y |
    y := x + 1.
    z := 42.
    ^ y

Depois da instrumentação

initialize
    <invariant: 'z = 42'>
    <instrumented>
    super initialize.
    z := 42.
    self afterInvariant: [ z = 42 ].
    
methodWithAssertions: x
    <require: 'x > 0'>
    <ensure: 'y = (x + 1)'>
    <instrumented>
    | y |
    self require: [ x > 0 ].
    self beforeInvariant: [ z = 42 ].
    y := x + 1.
    z := 42.
    self afterInvariant: [ z = 42 ].
    self ensure: [ y = (x + 1) ].
    ^ y.
    

O pragma <set:to:>

Na instrumentação envolvendo o pragma ensure muitas vezes precisamos expressar essa assertiva de forma dependente do estado de uma variável antes da execução do código de um método. Para efetivar isto usamos o pragma <set:to:> para obter o valor da variável no ínicio do método. Veja o exemplo abaixo.

Antes da instrumentação

methodWithAssertions: x
    <set: #old_z to: 'z'>
    <ensure: 'z = (old_z + 1)'>
    | y |
    y := x + 1.
    z := z + 666.
    ^ y

Depois da instrumentação

methodWithAssertions: x
    <set: #old_z to: 'z'>
    <ensure: 'z = (old_z + 1)'>
    <instrumented>
    | y old_z |
    old_z := z.
    y := x + 1.
    z := z + 666.
    self ensure: [ z = (old_z + 1) ].
    ^ y.
    

Em alguns casos é necessária uma cópia profunda do objeto antes da execução de um método, como no exemplo abaixo:

sort: anArray
   <set: #previous to: 'anArray veryDeepCopy'>
   <ensure: 'anArray asSet = previous asSet'>
   <ensure: 'anArray isSorted'>
   "código para ordenação"

Excluindo métodos da intrumentação de invariantes


Alguns métodos que são auxiliares na implementação de outros métodos e não fazem parte da interface pública a ser usada pelo código cliente não precisam respeitar os invariantes de classe. Para excluí-los da instrumentação de invariantes há dois pragmas para isso: exclude: e excludes: que devem ir no método initialize. Veja os exemplos abaixo:

initialize
    <exclude: #foo>
    <exclude: #bar>
    <invariant: 'z = 42'>
    z := 42

No exemplo acima os métodos foo e bar não serão instrumentados com invariantes embora possam ser intrumentados de acordo com pragmas require e ensure que porventura existam.

initialize
    <excludes: #(foo bar)>
    <invariant: 'z = 42'>
    z := 42

O exemplo acima mostra uma forma mais condensada onde um array literal contém os seletores dos métodos a serem excluidos.

Herança de assertivas

Herança de assertivas através da instrumentação é o próximo passo para completar o sistema de assertivas e instrumentação nos moldes da linguagem Eiffel. Brevemente…

File out

Abaixo segue o file-out que você pode instalar na sua imagem usando o File Browser:

Assertions.st

Error subclass: #AssertionViolation
	instanceVariableNames: ''
	classVariableNames: ''
	package: 'Assertions-Core'!

!AssertionViolation methodsFor: 'initialization' stamp: 'chicoary 10/6/2021 12:04'!
setMessageTextFromBlock: aBlock 
	self messageText: aBlock sourceNode sourceCode! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

AssertionViolation class
	instanceVariableNames: ''!

!AssertionViolation class methodsFor: 'as yet unclassified' stamp: 'chicoary 10/4/2021 11:29'!
block: aBlock 
	^ self new setMessageTextFromBlock: aBlock ! !


Object subclass: #Assertions
	instanceVariableNames: 'level'
	classVariableNames: 'Default Levels'
	package: 'Assertions-Core'!
!Assertions commentStamp: 'chicoary 10/6/2021 15:09' prior: 0!
Minha única instância `Assertions default` controla os níveis das assertivas implementadas como uma extensão do pacote `Assertions` na classe `Object`.

Os níveis possíveis são:
- none 
- require 
- ensure 
- invariant 
- all

Os métodos em `Object` que implementam as assertivas são:
- afterInvariant: 		"Usado somente na instrumentação"
- beforeInvariant: 	"Usado somente na instrumentação"
- ensure:
- invariant:for:
- invariants:for:
- onlyAfterInvariant:
- require:

Mais detalhes sobre o uso de `Assertions` podem ser encontrados em [Assertions no Pharo Smalltalk](https://chicoary.wordpress.com/2021/09/22/assertions-no-pharo-smalltalk/).!


!Assertions methodsFor: 'initialization' stamp: 'chicoary 9/22/2021 10:35'!
initialize 
	super initialize.
	level := Levels indexOf: #require
	! !


!Assertions methodsFor: 'testing' stamp: 'chicoary 9/22/2021 11:02'!
isEnsureLevel
	^ level >= (Levels indexOf: #ensure)! !

!Assertions methodsFor: 'testing' stamp: 'chicoary 9/22/2021 11:02'!
isInvariantLevel
	^ level >= (Levels indexOf: #invariant)! !

!Assertions methodsFor: 'testing' stamp: 'chicoary 9/22/2021 10:37'!
isRequireLevel
	^ level >= (Levels indexOf: #require)! !


!Assertions methodsFor: 'accessing' stamp: 'chicoary 9/22/2021 13:39'!
all
	level := Levels indexOf: #all! !

!Assertions methodsFor: 'accessing' stamp: 'chicoary 9/22/2021 13:38'!
on
	level := Levels indexOf: #require! !

!Assertions methodsFor: 'accessing' stamp: 'chicoary 9/22/2021 13:37'!
off
	level := Levels indexOf: #none! !

!Assertions methodsFor: 'accessing' stamp: 'chicoary 9/22/2021 13:36'!
beEnsureLevel
	level := Levels indexOf: #ensure! !

!Assertions methodsFor: 'accessing' stamp: 'chicoary 9/22/2021 13:39'!
beInvariantLevel
	level := Levels indexOf: #invariant! !

!Assertions methodsFor: 'accessing' stamp: 'chicoary 9/22/2021 13:37'!
beRequireLevel
	level := Levels indexOf: #require! !


"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Assertions class
	instanceVariableNames: ''!

!Assertions class methodsFor: 'accessing' stamp: 'chicoary 9/22/2021 13:41'!
all
	self default all! !

!Assertions class methodsFor: 'accessing' stamp: 'chicoary 9/22/2021 13:41'!
on
	self default on! !

!Assertions class methodsFor: 'accessing' stamp: 'chicoary 9/22/2021 10:29'!
default
	^ Default ifNil: [ Default := Assertions new ]! !

!Assertions class methodsFor: 'accessing' stamp: 'chicoary 9/22/2021 13:36'!
beEnsureLevel
	self default beEnsureLevel! !

!Assertions class methodsFor: 'accessing' stamp: 'chicoary 9/22/2021 13:40'!
beInvariantLevel
	self default beInvariantLevel! !

!Assertions class methodsFor: 'accessing' stamp: 'chicoary 9/22/2021 13:40'!
off
	self default off! !

!Assertions class methodsFor: 'accessing' stamp: 'chicoary 9/22/2021 13:40'!
beRequireLevel
	self default beRequireLevel! !


!Assertions class methodsFor: 'initialization' stamp: 'chicoary 9/22/2021 11:05'!
initialize 
	Levels := #(none require ensure invariant all).
	Default := nil.
	self inform: 'Initialized'! !


!Assertions class methodsFor: 'testing' stamp: 'chicoary 9/22/2021 14:11'!
isEnsureLevel
	^ self default isEnsureLevel ! !

!Assertions class methodsFor: 'testing' stamp: 'chicoary 9/22/2021 14:12'!
isInvariantLevel
	^ self default isInvariantLevel ! !

!Assertions class methodsFor: 'testing' stamp: 'chicoary 9/22/2021 14:10'!
isRequireLevel
	^ self default isRequireLevel ! !


!Assertions class methodsFor: 'as yet unclassified' stamp: 'chicoary 10/5/2021 07:52'!
instrumenter
	^ Instrumenter new! !

!Assertions class methodsFor: 'as yet unclassified' stamp: 'chicoary 10/6/2021 13:56'!
instrumentMethod: aMethod 
	self default instrumentMethod: aMethod ! !


AssertionViolation subclass: #EnsureViolation
	instanceVariableNames: ''
	classVariableNames: ''
	package: 'Assertions-Core'!

Assertions subclass: #Instrumenter
	instanceVariableNames: ''
	classVariableNames: ''
	package: 'Assertions-Core'!
!Instrumenter commentStamp: 'chicoary 10/6/2021 15:14' prior: 0!
Minhas instâncias são capazes de instrumentar um código inserindo assertivas nos locais adequados conforme `pragmas` inseridos no código.

Mais detalhes sobre o uso de `Assertions` e `Instrumenter` podem ser encontrados em [Assertions no Pharo Smalltalk](https://chicoary.wordpress.com/2021/09/22/assertions-no-pharo-smalltalk/).!


!Instrumenter methodsFor: 'instrumenting support' stamp: 'chicoary 10/7/2021 13:47'!
putAfterInvariantAssertionsOfMeyhod: aMethod on: stream
	self isInvariantLevel ifFalse: [ ^ self ].
	(self isExcludedMethod: aMethod) ifTrue: [ ^ self ].
	self put: #after invariantAssertionsOfMethod: aMethod on: stream! !

!Instrumenter methodsFor: 'instrumenting support' stamp: 'chicoary 10/5/2021 11:47'!
putSourceCodeOfStatements: statements on: stream

	statements do: [ :statement | 
		stream nextPutAll: statement sourceCode.
		stream nextPut: $..
		stream crtab ]! !

!Instrumenter methodsFor: 'instrumenting support' stamp: 'chicoary 10/6/2021 11:11'!
putEnsureAssertionsFromPragmas: pragmas on: stream
	self isEnsureLevel ifFalse: [ ^self ].
	self put: #ensure: assertionsFromPragmas: pragmas on: stream! !

!Instrumenter methodsFor: 'instrumenting support' stamp: 'chicoary 10/5/2021 13:19'!
put: beforeOrAfter invariantAssertionsOfMethod: aMethod on: stream

	| invariantPragmas intializePragmas |
	(aMethod methodClass includesSelector: #initialize) ifTrue: [ 
		intializePragmas := (aMethod methodClass >> #initialize) pragmas.
		invariantPragmas := intializePragmas select: [ :pragma | 
			                    pragma selector = #invariant: ].
		invariantPragmas do: [ :pragma | 
			stream nextPutAll: ('self {1}Invariant: [ {2} ]' format: { 
						 beforeOrAfter.
						 pragma arguments first }).
			stream nextPut: $..
			stream crtab ] ]! !

!Instrumenter methodsFor: 'instrumenting support' stamp: 'chicoary 10/5/2021 12:00'!
put: assertionSelector assertionsFromPragmas: pragmas on: stream

	| requirePragmas |
	requirePragmas := pragmas select: [ :pragma | 
		                  pragma selector = assertionSelector ].
	requirePragmas do: [ :pragma | 
		stream nextPutAll: ('self {1} [ {2} ]' format: { 
					 assertionSelector.
					 pragma arguments first sourceCode withoutQuoting }).
		stream nextPut: $..
		stream crtab ]! !

!Instrumenter methodsFor: 'instrumenting support' stamp: 'chicoary 10/5/2021 11:17'!
putSourceCodeOfPragmas: pragmas on: stream

	
	
	pragmas do: [ :pragma | 
		stream nextPutAll: pragma sourceCode.
		stream
			cr;
			tab ].
	! !

!Instrumenter methodsFor: 'instrumenting support' stamp: 'chicoary 10/5/2021 09:18'!
signatureOf: aMethod

	^ (Message
		   selector: aMethod selector
		   arguments: aMethod argumentNames) asString
		  copyReplaceAll: '#'
		  with: ''! !

!Instrumenter methodsFor: 'instrumenting support' stamp: 'chicoary 10/6/2021 11:04'!
putTemporaryNamesOfAST: ast on: stream

	| temporaryNames setPragmaNodes setTemporaryNames |
	temporaryNames := ast temporaryNames.
	self isEnsureLevel ifTrue: [  
		setTemporaryNames := ast pragmas select: [ :pragmaNode | pragmaNode selector = #set:to: ]
									thenCollect: [ :pragmaNode | (pragmaNode argumentAt: #set:) value ].
		temporaryNames addAll: setTemporaryNames.
	].	
	temporaryNames ifNotEmpty: [ 
		stream nextPut: $|.
		stream space.
		temporaryNames do: [ :temporaryName | 
			stream nextPutAll: temporaryName.
			stream space ].
		stream nextPut: $|.
		stream crtab ]! !

!Instrumenter methodsFor: 'instrumenting support' stamp: 'chicoary 10/5/2021 11:45'!
putReturnNodeFromStatements: statements on: stream

	| returnNode |
	returnNode := statements last.
	stream nextPutAll: returnNode sourceCode.
	stream nextPut: $..
	stream crtab! !

!Instrumenter methodsFor: 'instrumenting support' stamp: 'chicoary 10/5/2021 11:12'!
putSignatureOfMethod: aMethod on: stream

	| signature |
	signature := self signatureOf: aMethod.
	stream nextPutAll: signature.
	stream
		cr;
		tab! !

!Instrumenter methodsFor: 'instrumenting support' stamp: 'chicoary 10/6/2021 11:03'!
putSetStatementsFromPragmas: pragmas on: stream 
	self isEnsureLevel ifFalse: [ ^ self ].
	pragmas select: [ :pragma | pragma selector = #set:to: ] thenDo: [ :pragma | 
		stream nextPutAll: ('{1} := {2}' format: {
			(pragma argumentAt: #set:) value.
			(pragma argumentAt: #to:) value
		}).
		stream nextPut: $..
		stream crtab	
	].! !

!Instrumenter methodsFor: 'instrumenting support' stamp: 'chicoary 10/6/2021 10:59'!
putRequireAssertionsFromPragmas: pragmas on: stream
	self isRequireLevel ifFalse: [ ^ self ].
	self put: #require: assertionsFromPragmas: pragmas on: stream! !

!Instrumenter methodsFor: 'instrumenting support' stamp: 'chicoary 10/7/2021 14:00'!
putBeforeInvariantAssertionsOfMethod: aMethod on: stream
	self isInvariantLevel ifFalse: [ ^self ].
	(self isExcludedMethod: aMethod) ifTrue: [ ^ self ].
	self put: #before invariantAssertionsOfMethod: aMethod on: stream! !


!Instrumenter methodsFor: 'testing' stamp: 'chicoary 10/7/2021 14:36'!
hasInitializeInClass: aClass 
	^ (aClass methods collect: #selector) includes:  #initialize! !

!Instrumenter methodsFor: 'testing' stamp: 'chicoary 10/7/2021 13:55'!
isExcludedMethod: aMethod 
	| excludedMethods |
	(self hasInitializeInClass: aMethod methodClass) ifFalse: [ ^ false ].
	excludedMethods := (aMethod methodClass>>#initialize) pragmas 
		select: [ :pragma | #(exclude: excludes:) includes: pragma selector ] 
		thenCollect: [  :pragma | pragma arguments first ].
	^ excludedMethods flattened includes: aMethod selector! !

!Instrumenter methodsFor: 'testing' stamp: 'chicoary 10/6/2021 17:06'!
isInstrumentedMethod: aMethod 
	^ aMethod pragmas detect: [ :pragma | pragma selector = #instrumented ] ifFound: [ true ]  ifNone: [ false ]
! !


!Instrumenter methodsFor: 'instrumenting' stamp: 'chicoary 10/6/2021 16:46'!
instrumentInitializeMethodOfClass: aClass

	| initializeMethod ast pragmas statements instrumentedSource |

	self isInvariantLevel ifFalse: [ ^ self ].

	initializeMethod := aClass >> #initialize.
	ast := initializeMethod ast.
	self require: [ ast lastIsReturn not].
	instrumentedSource := String streamContents: [ :stream | 
		self putSignatureOfMethod: initializeMethod on: stream.
		pragmas := ast pragmas.
		self putSourceCodeOfPragmas: pragmas on: stream.
		self setAsInstrumentedOn: stream.
		self putTemporaryNamesOfAST: ast on: stream.
		statements := ast body statements.
		self putSourceCodeOfStatements: statements on: stream.
		self putAfterInvariantAssertionsOfMeyhod: initializeMethod on: stream
	].				                      
	initializeMethod methodClass compile: instrumentedSource! !

!Instrumenter methodsFor: 'instrumenting' stamp: 'chicoary 10/6/2021 19:47'!
restorePackage: aCategory 

	| splitted packageName tag |
	splitted := $- split: aCategory.
	packageName := splitted first.
	tag := $- join: splitted allButFirst. 
	packageName asPackage  definedClasses  select: [ :class | class tags includes: tag ] thenDo: [ :class | 
		self restoreClass: class
	]! !

!Instrumenter methodsFor: 'instrumenting' stamp: 'chicoary 10/6/2021 19:38'!
restoreClass: aClass 
	aClass methods do: [ :method | self restoreMethod: method ]! !

!Instrumenter methodsFor: 'instrumenting' stamp: 'chicoary 10/6/2021 13:56'!
instrumentClass: aClass 
	self instrumentInitializeMethodOfClass: aClass.
	aClass methods reject: [ :method | method selector = #initialize ] thenDo: [ :method | self instrumentMethod: method ]! !

!Instrumenter methodsFor: 'instrumenting' stamp: 'chicoary 10/6/2021 14:55'!
instrumentPackage: aCategory 
	| splitted packageName tag |
	splitted := $- split: aCategory.
	packageName := splitted first.
	tag := $- join: splitted allButFirst. 
	packageName asPackage  definedClasses  select: [ :class | class tags includes: tag ] thenDo: [ :class | 
		self instrumentClass: class
	]! !

!Instrumenter methodsFor: 'instrumenting' stamp: 'chicoary 10/6/2021 16:46'!
instrumentMethod: aMethod

	| ast pragmas statements lastIsReturn statementsWithoutReturn instrumentedSource |

	self require: [ aMethod selector ~= #initialize ].
	instrumentedSource := String streamContents: [ :stream | 
		self putSignatureOfMethod: aMethod on: stream.
		ast := aMethod ast.
		pragmas := ast pragmas.
		self putSourceCodeOfPragmas: pragmas on: stream.
		self setAsInstrumentedOn: stream.
		self putTemporaryNamesOfAST: ast on: stream.
		statements := ast body statements.
		lastIsReturn := ast body lastIsReturn.
		self putRequireAssertionsFromPragmas: pragmas on: stream.
		self putBeforeInvariantAssertionsOfMethod: aMethod on: stream.
		self putSetStatementsFromPragmas: pragmas on: stream.
		lastIsReturn
			ifTrue: [  
				statementsWithoutReturn := statements allButLast.
				self putSourceCodeOfStatements: statementsWithoutReturn on: stream.
				self putAfterInvariantAssertionsOfMeyhod: aMethod on: stream.
				self putEnsureAssertionsFromPragmas: pragmas on: stream.
				self putReturnNodeFromStatements: statements on: stream ]
			ifFalse: [  
				self putSourceCodeOfStatements: statements on: stream.
				self putAfterInvariantAssertionsOfMeyhod: aMethod on: stream.
				self putEnsureAssertionsFromPragmas: pragmas on: stream.
			].		                       ].
	aMethod methodClass compile: instrumentedSource.

	! !

!Instrumenter methodsFor: 'instrumenting' stamp: 'chicoary 10/6/2021 19:48'!
restoreMethod: aMethod 
	| rgMethod list sources before |
	
	(self isInstrumentedMethod: aMethod) ifFalse: [ ^self ].
	
	rgMethod := aMethod asRingDefinition asHistorical.
	list := (SourceFiles
		changeRecordsFrom: rgMethod sourcePointer
		className: rgMethod instanceSideParentName
		isMeta: rgMethod isMetaSide)
		collectWithIndex: [ :c :i | | rg |
			rg := c asRingDefinition.
			rg annotationNamed: #versionIndex put: i ].
	sources := list collect: #sourceCode.
	before := sources second.
	aMethod methodClass compile: before
	! !


!Instrumenter methodsFor: 'initialization' stamp: 'chicoary 10/6/2021 16:48'!
setAsInstrumentedOn: stream 
	stream nextPutAll: '<instrumented>'.
	stream crtab 
	
	! !

!Instrumenter methodsFor: 'initialization' stamp: 'chicoary 10/6/2021 12:17'!
initialize 
	super initialize.
	Assertions all! !


AssertionViolation subclass: #InvariantViolation
	instanceVariableNames: ''
	classVariableNames: ''
	package: 'Assertions-Core'!

InvariantViolation subclass: #AfterInvariantViolation
	instanceVariableNames: ''
	classVariableNames: ''
	package: 'Assertions-Core'!
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

AfterInvariantViolation class
	instanceVariableNames: ''!

!AfterInvariantViolation class methodsFor: 'as yet unclassified' stamp: 'chicoary 10/4/2021 11:29'!
block: aBlock 
	^ self new setMessageTextFromBlock: aBlock ! !


InvariantViolation subclass: #BeforeInvariantViolation
	instanceVariableNames: ''
	classVariableNames: ''
	package: 'Assertions-Core'!
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

BeforeInvariantViolation class
	instanceVariableNames: ''!

!BeforeInvariantViolation class methodsFor: 'as yet unclassified' stamp: 'chicoary 10/4/2021 11:29'!
block: aBlock 
	^ self new setMessageTextFromBlock: aBlock ! !


AssertionViolation subclass: #RequireViolation
	instanceVariableNames: ''
	classVariableNames: ''
	package: 'Assertions-Core'!
Assertions initialize!TestCase subclass: #EnsureViolationTest
	instanceVariableNames: ''
	classVariableNames: ''
	package: 'Assertions-Core-Tests'!
!EnsureViolationTest commentStamp: '<historical>' prior: 0!
An EnsureViolationTest is a test class for testing the behavior of EnsureViolation!


!EnsureViolationTest methodsFor: 'tests' stamp: 'chicoary 9/22/2021 14:07'!
testEnsure
	| answer |
	answer := 666.
	Assertions beEnsureLevel.
	self should: [
		self ensure: [  
			answer = 42	
		]
	] 
	raise: EnsureViolation 
! !


TestCase subclass: #InstrumentationTest
	instanceVariableNames: 'class category'
	classVariableNames: ''
	package: 'Assertions-Core-Tests'!

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/7/2021 05:06'!
testPackageInstrumentation

	| source initializeSource |
	
	initializeSource := '
initialize 
	<invariant: ''z = 42''>
	super initialize. 
	z := 42'.
	
	source := '
methodWithAssertions: x
	<require: ''x > 0''>
	<ensure: ''y = (x + 1)''>
	| y |
	y := x + 1.
	z := 42.
	^ y
'.

	class addInstVarNamed: 'z'.
	class compile: initializeSource.
	class compile: source.
	Assertions instrumenter 
		all;
		instrumentPackage: category.  
	self shouldnt: [ class new initialize ] raise: AfterInvariantViolation.
	self shouldnt: [  class new methodWithAssertions: 42 ] raise: AfterInvariantViolation
	! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/6/2021 13:56'!
testRequire
	| source |
	source := '
methodWithAssertions: x
	<require: ''x > 0''>
	| y |
	y := x + 1.
	^ y
'.

	class compile: source.
	Assertions instrumenter instrumentMethod: (class>>#methodWithAssertions:).
	self should: [  class new methodWithAssertions: -42 ] raise: RequireViolation
	! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/7/2021 13:27'!
testExclude
	| initializeSource fooSource barSource |
	initializeSource := '
initialize
	<exclude: #bar>
	<invariant: ''z = 42''>
	z := 42
'.

fooSource := '
foo
	z := 666
'.

barSource := '
bar
	z := 666
'.
	class addInstVarNamed: 'z'.
	class compile: initializeSource.
	class compile: fooSource.
	class compile: barSource.
	Assertions instrumenter 
		all;
		instrumentClass: class.
		
	self shouldnt: [ class new initialize ] raise: InvariantViolation.
	self should: [ class new foo ] raise: InvariantViolation.
	self shouldnt: [ class new bar ] raise: InvariantViolation.! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/6/2021 13:55'!
testRequireLevel

	| source initializeSource instrumenter |
	initializeSource := '
initialize 
	<invariant: ''z = 42''>
	super initialize. 
	z := 42'.

	source := '
methodWithAssertions: x
	<require: ''x > 0''>
	<ensure: ''y = (x + 1)''>
	| y |
	y := x + 2. "Ensure violation"
	z := 666. "Invariant violation"
	^ y
'.

	class addInstVarNamed: 'z'.
	class compile: initializeSource.
	class compile: source.
	instrumenter := Assertions instrumenter.
	instrumenter beRequireLevel.
	instrumenter instrumentClass: class.
	self shouldnt: [ class new initialize ] raise: AfterInvariantViolation.
	self should: [ class new methodWithAssertions: -42 ] raise: RequireViolation.
	self shouldnt: [ class new methodWithAssertions: 42 ] raise: InvariantViolation.
	self shouldnt: [ class new methodWithAssertions: 42 ] raise: EnsureViolation.
	! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/6/2021 13:55'!
testEnsureLevel

	| source initializeSource instrumenter |
	initializeSource := '
initialize 
	<invariant: ''z = 42''>
	super initialize. 
	z := 42'.

	source := '
methodWithAssertions: x
	<require: ''x > 0''>
	<ensure: ''y = (x + 1)''>
	| y |
	y := x + 2. "Ensure violation"
	z := 666. "Invariant violation"
	^ y
'.

	class addInstVarNamed: 'z'.
	class compile: initializeSource.
	class compile: source.
	instrumenter := Assertions instrumenter.
	instrumenter beEnsureLevel.
	instrumenter instrumentClass: class.
	self shouldnt: [ class new initialize ] raise: AfterInvariantViolation.
	self should: [ class new methodWithAssertions: -42 ] raise: RequireViolation.
	self should: [ class new methodWithAssertions: 42 ] raise: EnsureViolation
	
	! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/6/2021 19:35'!
testRestoreClass
	| source initializeSource formattedCode initializeFormattedSource |
	
	initializeSource := '
initialize 
	<invariant: ''z = 42''>
	super initialize. 
	z := 42'.
	
	source := '
methodWithAssertions: x
	<require: ''x > 0''>
	<ensure: ''y = (x + 1)''>
	| y |
	y := x + 1.
	z := 42.
	^ y
'.

	class addInstVarNamed: 'z'.
	initializeFormattedSource := (class>>(class compile: initializeSource)) ast formattedCode.
	formattedCode := (class>>(class compile: source)) ast formattedCode.
	Assertions instrumenter instrumentClass: class. 
	Assertions instrumenter restoreClass: class.
	
	self assert: (class>>#methodWithAssertions:) ast formattedCode equals: formattedCode.
	self assert: (class>>#initialize) ast formattedCode equals: initializeFormattedSource.
	
	! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/6/2021 13:56'!
testInvariant
	| source initializeSource |
	
	initializeSource := '
initialize 
	<invariant: ''z = 42''>
	super initialize. 
	z := 42'.
	
	source := '
methodWithoutAssertions: x
	| y |
	y := x + 1.
	z := 0.
	^ y
'.

	class addInstVarNamed: 'z'.
	class compile: initializeSource.
	class compile: source.
	Assertions instrumenter
		all;
		instrumentInitializeMethodOfClass: class;
		instrumentMethod: (class>>#methodWithoutAssertions:).
	self shouldnt: [ class new initialize ] raise: AfterInvariantViolation.
	self should: [  class new methodWithoutAssertions: 42 ] raise: AfterInvariantViolation
	! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/7/2021 13:51'!
testExcludes

	| initializeSource fooSource barSource bazSource |
	initializeSource := '
initialize
	<excludes: #(bar baz)>
	<invariant: ''z = 42''>
	z := 42
'.

fooSource := '
foo
	z := 666
'.

barSource := '
bar
	z := 666
'.

bazSource := '
baz
	z := 666
'.

	class addInstVarNamed: 'z'.
	class compile: initializeSource.
	class compile: fooSource.
	class compile: barSource.
	class compile: bazSource.
	Assertions instrumenter 
		all;
		instrumentClass: class.
		
	self shouldnt: [ class new initialize ] raise: InvariantViolation.
	self should: [ class new foo ] raise: InvariantViolation.
	self shouldnt: [ class new bar ] raise: InvariantViolation.
	self shouldnt: [ class new baz ] raise: InvariantViolation.! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/6/2021 16:32'!
testRestoreMethod

	| source initializeSource formattedCode initializeFormattedSource |
	
	initializeSource := '
initialize 
	<invariant: ''z = 42''>
	super initialize. 
	z := 42'.
	
	source := '
methodWithAssertions: x
	<require: ''x > 0''>
	<ensure: ''y = (x + 1)''>
	| y |
	y := x + 1.
	z := 42.
	^ y
'.

	class addInstVarNamed: 'z'.
	initializeFormattedSource := (class>>(class compile: initializeSource)) ast formattedCode.
	formattedCode := (class>>(class compile: source)) ast formattedCode.
	Assertions instrumenter 
		all;
		instrumentInitializeMethodOfClass: class;
		instrumentMethod: (class>>#methodWithAssertions:).
	Assertions instrumenter restoreMethod: (class>>#methodWithAssertions:).
	Assertions instrumenter restoreMethod: class>>#initialize.
	
	self assert: (class>>#methodWithAssertions:) ast formattedCode equals: formattedCode.
	self assert: (class>>#initialize) ast formattedCode equals: initializeFormattedSource.
	! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/7/2021 05:05'!
testEnsure
	| source |
	source := '
methodWithAssertions: x
	<ensure: ''y = (x + 1)''>
	| y |
	y := x + 2.
	^ y
'.

	class compile: source.
	Assertions instrumenter 
		all; 
		instrumentMethod: (class>>#methodWithAssertions:).
	self should: [  class new methodWithAssertions: 42 ] raise: EnsureViolation
	! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/6/2021 19:45'!
testRestorePackage

	| source initializeSource initializeFormattedSource formattedCode |
	
	initializeSource := '
initialize 
	<invariant: ''z = 42''>
	super initialize. 
	z := 42'.
	
	source := '
methodWithAssertions: x
	<require: ''x > 0''>
	<ensure: ''y = (x + 1)''>
	| y |
	y := x + 1.
	z := 42.
	^ y
'.

	class addInstVarNamed: 'z'.
	initializeFormattedSource := (class>>(class compile: initializeSource)) ast formattedCode.
	formattedCode := (class>>(class compile: source)) ast formattedCode.
	Assertions instrumenter instrumentPackage: category.
	Assertions instrumenter restorePackage: category. 
	
	self assert: (class>>#methodWithAssertions:) ast formattedCode equals: formattedCode.
	self assert: (class>>#initialize) ast formattedCode equals: initializeFormattedSource. 
	
	! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/6/2021 13:55'!
testInvariantLevel

	| source initializeSource instrumenter |
	initializeSource := '
initialize 
	<invariant: ''z = 42''>
	super initialize. 
	z := 42'.

	source := '
methodWithAssertions: x
	<require: ''x > 0''>
	<ensure: ''y = (x + 1)''>
	| y |
	y := x + 1. 
	z := 666. "Invariant violation"
	^ y
'.

	class addInstVarNamed: 'z'.
	class compile: initializeSource.
	class compile: source.
	instrumenter := Assertions instrumenter.
	instrumenter beInvariantLevel.
	instrumenter instrumentClass: class.
	self shouldnt: [ class new initialize ] raise: AfterInvariantViolation.
	self should: [ class new methodWithAssertions: -42 ] raise: RequireViolation.
	self should: [ class new methodWithAssertions: 42 ] raise: InvariantViolation.
	
	! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/7/2021 04:56'!
testAllAssertionPragmas
	| source initializeSource |
	
	initializeSource := '
initialize 
	<invariant: ''z = 42''>
	super initialize. 
	z := 42'.
	
	source := '
methodWithAssertions: x
	<require: ''x > 0''>
	<ensure: ''y = (x + 1)''>
	| y |
	y := x + 1.
	z := 42.
	^ y
'.

	class addInstVarNamed: 'z'.
	class compile: initializeSource.
	class compile: source.
	Assertions instrumenter 
		all;
		instrumentInitializeMethodOfClass: class;
		instrumentMethod: (class>>#methodWithAssertions:).
	self shouldnt: [ class new initialize ] raise: AfterInvariantViolation.
	self shouldnt: [  class new methodWithAssertions: 42 ] raise: AfterInvariantViolation
	! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/7/2021 05:05'!
testEnsureWithOld
	| source initializeSource |
	
	initializeSource := '
initialize 
	super initialize. 
	z := 41'.
	
	source := '
methodWithAssertions: x
	<set: #old_z to: ''z''>
	<ensure: ''z = (old_z + 1)''>
	| y |
	y := x + 1.
	z := z + 666.
	^ y
'.
	
	class addInstVarNamed: 'z'.
	class compile: initializeSource.
	class compile: source.	
	Assertions instrumenter 
		all; 
		instrumentMethod: (class>>#methodWithAssertions:).
	self should: [  class new methodWithAssertions: 42 ] raise: EnsureViolation
	! !

!InstrumentationTest methodsFor: 'tests' stamp: 'chicoary 10/7/2021 05:04'!
testClassInstrumentation
	| source initializeSource |
	
	initializeSource := '
initialize 
	<invariant: ''z = 42''>
	super initialize. 
	z := 42'.
	
	source := '
methodWithAssertions: x
	<require: ''x > 0''>
	<ensure: ''y = (x + 1)''>
	| y |
	y := x + 1.
	z := 42.
	^ y
'.

	class addInstVarNamed: 'z'.
	class compile: initializeSource.
	class compile: source.
	Assertions instrumenter
		all;
		instrumentClass: class. 
	self shouldnt: [ class new initialize ] raise: AfterInvariantViolation.
	self shouldnt: [  class new methodWithAssertions: 42 ] raise: AfterInvariantViolation
	! !


!InstrumentationTest methodsFor: 'initialization' stamp: 'chicoary 10/4/2021 12:03'!
tearDown 
	Smalltalk removeClassNamed: class name! !

!InstrumentationTest methodsFor: 'initialization' stamp: 'chicoary 10/6/2021 14:52'!
setUp

	class := Object subclass: #ClassForInstrumentationTests.
	category := 'Assertions-Core-Tests-Temporary'.
	class category: category, 'Test'. 
	"Assertions all"! !


TestCase subclass: #InvariantViolationTest
	instanceVariableNames: ''
	classVariableNames: ''
	package: 'Assertions-Core-Tests'!
!InvariantViolationTest commentStamp: '<historical>' prior: 0!
An InvariantViolationTest is a test class for testing the behavior of InvariantViolation!


!InvariantViolationTest methodsFor: 'tests' stamp: 'chicoary 10/4/2021 09:22'!
testMultipleInvariantSuccessful
	| answer |
	answer := 42.
	self shouldnt: [  
		self invariants: {  
			[ answer isNotNil ].
			[ answer = 42 ].
		} for: [  
			answer := 42
		]
	] raise: InvariantViolation  
	! !

!InvariantViolationTest methodsFor: 'tests' stamp: 'chicoary 10/4/2021 10:09'!
testMultipleInvariantFailAfter
	| answer |
	answer := 42.
	self should: [  
		self invariants: {  
			[ answer isNotNil ].
			[ answer = 42 ].
		} for: [  
			answer := 666
		]
	] raise: AfterInvariantViolation ! !

!InvariantViolationTest methodsFor: 'tests' stamp: 'chicoary 9/22/2021 14:07'!
testInvariantBefore
	| answer |
	answer := 666.
	Assertions beInvariantLevel.
	self should: [
		self invariant: [ answer = 42 ] for: [  
			answer := 42	
		]
	] 
	raise: BeforeInvariantViolation 
! !

!InvariantViolationTest methodsFor: 'tests' stamp: 'chicoary 9/22/2021 14:07'!
testInvariantAfter
	| answer |
	answer := 42.
	Assertions beInvariantLevel.
	self should: [
		self invariant: [ answer = 42 ] for: [  
			answer := 666	
		]
	] 
	raise: AfterInvariantViolation 
! !

!InvariantViolationTest methodsFor: 'tests' stamp: 'chicoary 10/4/2021 09:33'!
testMultipleInvariantFailBefore
	| answer |
	answer := nil.
	self should: [  
		self invariants: {  
			[ answer isNotNil ].
			[ answer = 42 ].
		} for: [  
			answer := 42
		]
	] raise: BeforeInvariantViolation 
	! !

!InvariantViolationTest methodsFor: 'tests' stamp: 'chicoary 9/22/2021 14:42'!
testInvariantOnlyAfter
	| answer |
	answer := 42.
	Assertions beInvariantLevel.
	self should: [
		self onlyAfterInvariant: [ answer = 42 ] for: [  
			answer := 666	
		]
	] 
	raise: AfterInvariantViolation.
	
	answer := 666.
	self shouldnt: [
		self onlyAfterInvariant: [ answer = 42 ] for: [  
			answer := 42	
		]
	] 
	raise: AfterInvariantViolation 
! !


TestCase subclass: #LevelsTest
	instanceVariableNames: ''
	classVariableNames: ''
	package: 'Assertions-Core-Tests'!

!LevelsTest methodsFor: 'tests' stamp: 'chicoary 10/4/2021 10:22'!
testLevelOn
	Assertions on.
	self should: [ self require: [ false ] ] raise: RequireViolation.
	self shouldnt: [ self ensure: [ false ] ] raise: EnsureViolation.
	self shouldnt: [ self invariant: [ false ] for: [  ] ] raise: InvariantViolation.
	self shouldnt: [ self invariants: {[ false ]} for: [  ] ] raise: InvariantViolation.! !

!LevelsTest methodsFor: 'tests' stamp: 'chicoary 10/4/2021 10:16'!
testLevelNone
	Assertions off.
	self shouldnt: [ self require: [ false ] ] raise: RequireViolation.
	self shouldnt: [ self ensure: [ false ] ] raise: EnsureViolation.
	self shouldnt: [ self invariant: [ false ] for: [  ] ] raise: InvariantViolation.
	self shouldnt: [ self invariants: {[ false ]} for: [  ] ] raise: InvariantViolation.! !

!LevelsTest methodsFor: 'tests' stamp: 'chicoary 10/4/2021 10:17'!
testLevelRequire
	Assertions beRequireLevel.
	self should: [ self require: [ false ] ] raise: RequireViolation.
	self shouldnt: [ self ensure: [ false ] ] raise: EnsureViolation.
	self shouldnt: [ self invariant: [ false ] for: [  ] ] raise: InvariantViolation.
	self shouldnt: [ self invariants: {[ false ]} for: [  ] ] raise: InvariantViolation.! !

!LevelsTest methodsFor: 'tests' stamp: 'chicoary 10/4/2021 10:20'!
testLevelInvariant
	Assertions beInvariantLevel.
	self should: [ self require: [ false ] ] raise: RequireViolation.
	self should: [ self ensure: [ false ] ] raise: EnsureViolation.
	self should: [ self invariant: [ false ] for: [  ] ] raise: InvariantViolation.
	self should: [ self invariants: {[ false ]} for: [  ] ] raise: InvariantViolation.! !

!LevelsTest methodsFor: 'tests' stamp: 'chicoary 10/4/2021 10:20'!
testLevelAll
	Assertions all.
	self should: [ self require: [ false ] ] raise: RequireViolation.
	self should: [ self ensure: [ false ] ] raise: EnsureViolation.
	self should: [ self invariant: [ false ] for: [  ] ] raise: InvariantViolation.
	self should: [ self invariants: {[ false ]} for: [  ] ] raise: InvariantViolation.! !

!LevelsTest methodsFor: 'tests' stamp: 'chicoary 10/4/2021 10:19'!
testLevelEnsure
	Assertions beEnsureLevel.
	self should: [ self require: [ false ] ] raise: RequireViolation.
	self should: [ self ensure: [ false ] ] raise: EnsureViolation.
	self shouldnt: [ self invariant: [ false ] for: [  ] ] raise: InvariantViolation.
	self shouldnt: [ self invariants: {[ false ]} for: [  ] ] raise: InvariantViolation.! !


TestCase subclass: #RequireViolationTest
	instanceVariableNames: ''
	classVariableNames: ''
	package: 'Assertions-Core-Tests'!
!RequireViolationTest commentStamp: '<historical>' prior: 0!
A RequireViolationTest is a test class for testing the behavior of RequireViolation!


!RequireViolationTest methodsFor: 'tests' stamp: 'chicoary 9/22/2021 13:25'!
testRequire
	| answer |
	answer := 666.
	self should: [
		self require: [  
			answer = 42	
		]
	] 
	raise: RequireViolation 
! !
'From Pharo9.0.0 of 17 September 2021 [Build information: Pharo-9.0.0+build.1549.sha.eae2e955c11d5c166543f2fc903c4bccf3e2b8f4 (64 Bit)] on 7 October 2021 at 7:55:34.956875 pm'!

!Object methodsFor: '*Assertions' stamp: 'chicoary 10/6/2021 11:32'!
invariants: anInvariantList for: aCodeBlock 
	<debuggerCompleteToSender>

	Assertions isInvariantLevel ifFalse: [ ^ self ].
	anInvariantList do:  [ :invariant |  
		invariant value ifFalse: [ (BeforeInvariantViolation block: invariant) signal ]
	].
	aCodeBlock value.
	anInvariantList do:  [ :invariant |  
		invariant value ifFalse: [ (AfterInvariantViolation block: invariant) signal ]
	]! !
'From Pharo9.0.0 of 17 September 2021 [Build information: Pharo-9.0.0+build.1549.sha.eae2e955c11d5c166543f2fc903c4bccf3e2b8f4 (64 Bit)] on 7 October 2021 at 7:55:34.95874 pm'!

!Object methodsFor: '*Assertions' stamp: 'chicoary 10/6/2021 11:31'!
ensure: aBlock 
	<debuggerCompleteToSender>
	Assertions isEnsureLevel ifFalse: [ ^ self ].
	aBlock value ifFalse: [ (EnsureViolation block: aBlock) signal ]
	
	! !
'From Pharo9.0.0 of 17 September 2021 [Build information: Pharo-9.0.0+build.1549.sha.eae2e955c11d5c166543f2fc903c4bccf3e2b8f4 (64 Bit)] on 7 October 2021 at 7:55:34.960244 pm'!

!Object methodsFor: '*Assertions' stamp: 'chicoary 10/5/2021 13:27'!
require: aBlock
	<debuggerCompleteToSender>
	Assertions isRequireLevel ifFalse: [ ^ self ].
	aBlock value ifFalse: [ (RequireViolation block: aBlock) signal ]! !
'From Pharo9.0.0 of 17 September 2021 [Build information: Pharo-9.0.0+build.1549.sha.eae2e955c11d5c166543f2fc903c4bccf3e2b8f4 (64 Bit)] on 7 October 2021 at 7:55:34.961374 pm'!

!Object methodsFor: '*Assertions' stamp: 'chicoary 10/5/2021 13:28'!
afterInvariant: aBlock 
	<debuggerCompleteToSender>
	Assertions isInvariantLevel ifFalse: [ ^ self ].
	aBlock value ifFalse: [ (AfterInvariantViolation block: aBlock) signal ]! !
'From Pharo9.0.0 of 17 September 2021 [Build information: Pharo-9.0.0+build.1549.sha.eae2e955c11d5c166543f2fc903c4bccf3e2b8f4 (64 Bit)] on 7 October 2021 at 7:55:34.962193 pm'!

!Object methodsFor: '*Assertions' stamp: 'chicoary 10/6/2021 11:31'!
invariant: aBlock for: aCodeBlock 
    <debuggerCompleteToSender>
    Assertions isInvariantLevel ifFalse: [ ^ self ].
	aBlock value ifFalse: [ (BeforeInvariantViolation block: aBlock) signal ].
   aCodeBlock value.
   aBlock value ifFalse: [ (AfterInvariantViolation block: aBlock) signal ].! !
'From Pharo9.0.0 of 17 September 2021 [Build information: Pharo-9.0.0+build.1549.sha.eae2e955c11d5c166543f2fc903c4bccf3e2b8f4 (64 Bit)] on 7 October 2021 at 7:55:34.963129 pm'!

!Object methodsFor: '*Assertions' stamp: 'chicoary 10/5/2021 13:28'!
beforeInvariant: aBlock 
	<debuggerCompleteToSender>
	Assertions isInvariantLevel ifFalse: [ ^ self ].
	aBlock value ifFalse: [ (BeforeInvariantViolation block: aBlock) signal ]! !
'From Pharo9.0.0 of 17 September 2021 [Build information: Pharo-9.0.0+build.1549.sha.eae2e955c11d5c166543f2fc903c4bccf3e2b8f4 (64 Bit)] on 7 October 2021 at 7:55:34.964051 pm'!

!Object methodsFor: '*Assertions' stamp: 'chicoary 10/6/2021 11:33'!
onlyAfterInvariant: aBlock for: aCodeBlock 
    <debuggerCompleteToSender>
    Assertions isInvariantLevel ifFalse: [ ^ self ].
    aCodeBlock value.
    aBlock value ifFalse: [ (AfterInvariantViolation block: aBlock) signal ]
   ! !

Deixe um comentário