Compare commits

..

6 Commits

Author SHA1 Message Date
235910b863 Be better on startup 2022-06-14 16:28:44 +02:00
33cb150cf0 Be better on startup 2022-06-14 16:25:53 +02:00
66fe79f2bf Fix metacello load order 2022-06-14 16:10:55 +02:00
d75b000ad1 A better IDE 2022-06-14 15:54:07 +02:00
22d00d0360 Add coder 2022-06-14 00:05:36 +02:00
8da76b5a3f Stop carp application on image restart 2022-06-13 22:54:57 +02:00
39 changed files with 506 additions and 130 deletions

View File

@@ -103,14 +103,14 @@
"__type" : "time",
"time" : {
"__type" : "dateAndTime",
"dateAndTimeString" : "2022-04-17T19:36:14.725535+02:00"
"dateAndTimeString" : "2022-06-13T22:57:31.662829+02:00"
}
},
"uid" : {
"__type" : "uid",
"uidString" : "yC3J0D6ZDQCd0ZgmDqn2mw=="
},
"code" : "'Example' asCarpModule\r\taddExpression: (CarpStaticFunction\r\t\t\t named: 'example' asCarpSymbol\r\t\t\t withArguments: { \r\t\t\t\t\t 'x' asCarpSymbol.\r\t\t\t\t\t 'y' asCarpSymbol }\r\t\t\t andBody: (CarpCall function: '+' asCarpSymbol arguments: { \r\t\t\t\t\t\t\t 'x' asCarpSymbol.\r\t\t\t\t\t\t\t 'y' asCarpSymbol }));\r\taddExpression: (CarpDynamicVariable\r\t\t\t named: 'dyn-example' asCarpSymbol\r\t\t\t binding: 1 asCarpInteger);\r\ttoCarp"
"code" : "'Example' asCarpModule\r\taddExpression: (CarpStaticFunction\r\t\t\t named: 'example' asCarpSymbol\r\t\t\t withArguments: { \r\t\t\t\t\t 'x' asCarpSymbol.\r\t\t\t\t\t 'y' asCarpSymbol }\r\t\t\t andBody: {}'+' asCarpSymbol arguments: { \r\t\t\t\t\t\t\t 'x' asCarpSymbol.\r\t\t\t\t\t\t\t 'y' asCarpSymbol }));\r\taddExpression: (CarpDynamicVariable\r\t\t\t named: 'dyn-example' asCarpSymbol\r\t\t\t binding: 1 asCarpInteger);\r\ttoCarp"
},
{
"__type" : "textSnippet",
@@ -248,7 +248,7 @@
"__type" : "time",
"time" : {
"__type" : "dateAndTime",
"dateAndTimeString" : "2022-04-17T19:40:10.759445+02:00"
"dateAndTimeString" : "2022-04-17T19:40:21.249005+02:00"
}
},
"uid" : {
@@ -258,7 +258,7 @@
"paragraphStyle" : {
"__type" : "textStyle"
},
"string" : "In the next chapter, we will use this code generator in our newly created coder"
"string" : "In the next chapter named [[A coder of ones own]], we will use this code generator in our newly created coder."
}
]
},

View File

@@ -103,14 +103,14 @@
"__type" : "time",
"time" : {
"__type" : "dateAndTime",
"dateAndTimeString" : "2022-04-17T19:36:14.725535+02:00"
"dateAndTimeString" : "2022-06-13T22:57:42.883096+02:00"
}
},
"uid" : {
"__type" : "uid",
"uidString" : "yC3J0D6ZDQCd0ZgmDqn2mw=="
},
"code" : "'Example' asCarpModule\r\taddExpression: (CarpStaticFunction\r\t\t\t named: 'example' asCarpSymbol\r\t\t\t withArguments: { \r\t\t\t\t\t 'x' asCarpSymbol.\r\t\t\t\t\t 'y' asCarpSymbol }\r\t\t\t andBody: (CarpCall function: '+' asCarpSymbol arguments: { \r\t\t\t\t\t\t\t 'x' asCarpSymbol.\r\t\t\t\t\t\t\t 'y' asCarpSymbol }));\r\taddExpression: (CarpDynamicVariable\r\t\t\t named: 'dyn-example' asCarpSymbol\r\t\t\t binding: 1 asCarpInteger);\r\ttoCarp"
"code" : "'Example' asCarpModule\r\taddExpression: (CarpStaticFunction\r\t\t\t named: 'example' asCarpSymbol\r\t\t\t withArguments: { \r\t\t\t\t\t 'x' asCarpSymbol.\r\t\t\t\t\t 'y' asCarpSymbol }\r\t\t\t andBody: {'+' asCarpSymbol .\r\t\t\t\t\t\t\t 'x' asCarpSymbol.\r\t\t\t\t\t\t\t 'y' asCarpSymbol } asCarpCall);\r\taddExpression: (CarpDynamicVariable\r\t\t\t named: 'dyn-example' asCarpSymbol\r\t\t\t binding: 1 asCarpInteger);\r\ttoCarp"
},
{
"__type" : "textSnippet",

View File

@@ -13,6 +13,6 @@ BaselineOfCarp >> baseline: spec [
baseline: 'GToolkit4SmaCC'
with: [ spec repository: 'github://feenkcom/gt4smacc:main/src' ].
spec package: 'Carp' with: [ spec requires: #('GToolkit4SmaCC') ].
spec package: 'Carp-Parser' with: [ spec requires: #('GToolkit4SmaCC') ].
spec package: 'Carp-AST' with: [ spec requires: #('GToolkit4SmaCC') ] ]
spec package: 'Carp-AST' with: [ spec requires: #('GToolkit4SmaCC') ].
spec package: 'Carp-Parser' with: [ spec requires: #('GToolkit4SmaCC') ] ]
]

View File

@@ -13,6 +13,11 @@ CarpCharacterNode >> acceptVisitor: anExpressionVisitor [
^ anExpressionVisitor visitCharacter: self
]
{ #category : #accessing }
CarpCharacterNode >> intoModel [
^ CarpCharacter character: self value source asCharacter
]
{ #category : #accessing }
CarpCharacterNode >> toPharo [
^ value source asCharacter

View File

@@ -21,6 +21,11 @@ CarpExpressionNode >> isDefinition [
^ false
]
{ #category : #accessing }
CarpExpressionNode >> isDefinitionPredicate [
^ false
]
{ #category : #accessing }
CarpExpressionNode >> isQuoted [
^ parent ifNil: [ false ] ifNotNil: [ parent isQuoted ]

View File

@@ -13,6 +13,11 @@ CarpNumberNode >> acceptVisitor: anExpressionVisitor [
^ anExpressionVisitor visitNumber: self
]
{ #category : #accessing }
CarpNumberNode >> intoModel [
^ CarpDouble number: self value source asNumber
]
{ #category : #accessing }
CarpNumberNode >> toPharo [
^ value source asInteger

View File

@@ -39,6 +39,12 @@ CarpStartNode >> initialize [
expressions := OrderedCollection new: 2.
]
{ #category : #accessing }
CarpStartNode >> intoModel [
self assert: self expressions size = 1.
^ self expressions first intoModel
]
{ #category : #accessing }
CarpStartNode >> toPharo [
^ expressions collect: #toPharo

View File

@@ -13,6 +13,11 @@ CarpStringNode >> acceptVisitor: anExpressionVisitor [
^ anExpressionVisitor visitString: self
]
{ #category : #accessing }
CarpStringNode >> intoModel [
^ CarpStringExpression contents: self value source
]
{ #category : #accessing }
CarpStringNode >> toPharo [
^ value source

View File

@@ -13,6 +13,11 @@ CarpVariableNode >> acceptVisitor: anExpressionVisitor [
^ anExpressionVisitor visitVariable: self
]
{ #category : #accessing }
CarpVariableNode >> intoModel [
^ CarpSymbol named: self value source
]
{ #category : #accessing }
CarpVariableNode >> isDefinitionPredicate [
^ {'defdynamic'.

View File

@@ -41,6 +41,11 @@ CarpArrayNode >> initialize [
expressions := OrderedCollection new: 2.
]
{ #category : #accessing }
CarpArrayNode >> intoModel [
^ CarpArray contents: (expressions collect: #intoModel)
]
{ #category : #generated }
CarpArrayNode >> leftBracket [

View File

@@ -26,6 +26,11 @@ CarpDerefNode >> derefGlyph: aSmaCCToken [
derefGlyph := aSmaCCToken
]
{ #category : #accessing }
CarpDerefNode >> intoModel [
^ CarpCall function: 'deref' arguments: {value intoModel}
]
{ #category : #generated }
CarpDerefNode >> nodeVariables [

View File

@@ -49,6 +49,22 @@ CarpListNode >> initialize [
expressions := OrderedCollection new: 2.
]
{ #category : #accessing }
CarpListNode >> intoModel [
^ self isDefinition
ifTrue: [ | binding |
binding := (CarpBinding perform: self expressions first value source asSymbol)
name: self definitionVariable intoModel.
self expressions size = 3
ifTrue: [ binding binding: self expressions third intoModel ].
self expressions size = 4
ifTrue: [ binding
arguments: self expressions third intoModel;
body: self expressions fourth intoModel ].
binding ]
ifFalse: [ CarpList contents: (expressions collect: #intoModel) ]
]
{ #category : #accessing }
CarpListNode >> isDefinition [
^ self definitionVariable isNotNil

View File

@@ -27,6 +27,15 @@ CarpMapNode >> initialize [
pairs := OrderedCollection new: 2.
]
{ #category : #accessing }
CarpMapNode >> intoModel [
^ CarpMap
contents: (pairs
flatCollect: [ :p |
{p key intoModel.
p value intoModel} ])
]
{ #category : #generated }
CarpMapNode >> leftBrace [

View File

@@ -14,6 +14,14 @@ CarpModuleOrTypeNode >> acceptVisitor: anExpressionVisitor [
^ anExpressionVisitor visitModuleOrType: self
]
{ #category : #accessing }
CarpModuleOrTypeNode >> intoModel [
^ CarpSymbol
named: ('.'
join: {module source.
value source})
]
{ #category : #generated }
CarpModuleOrTypeNode >> module [

View File

@@ -14,6 +14,11 @@ CarpRefCallNode >> acceptVisitor: anExpressionVisitor [
^ anExpressionVisitor visitRefCall: self
]
{ #category : #accessing }
CarpRefCallNode >> intoModel [
^ CarpCall function: '~' arguments: {value intoModel}
]
{ #category : #generated }
CarpRefCallNode >> nodeVariables [

View File

@@ -14,6 +14,11 @@ CarpRefNode >> acceptVisitor: anExpressionVisitor [
^ anExpressionVisitor visitRef: self
]
{ #category : #accessing }
CarpRefNode >> intoModel [
^ CarpCall function: 'ref' arguments: {value intoModel}
]
{ #category : #generated }
CarpRefNode >> nodeVariables [

View File

@@ -14,6 +14,11 @@ CarpUnquoteNode >> acceptVisitor: anExpressionVisitor [
^ anExpressionVisitor visitUnquote: self
]
{ #category : #accessing }
CarpUnquoteNode >> intoModel [
^ CarpCall function: 'unquote' arguments: {value intoModel}
]
{ #category : #accessing }
CarpUnquoteNode >> isQuoted [
^ false

View File

@@ -13,6 +13,11 @@ CarpApplication class >> start [
^ self startWith: LanguageLinkSettings carpDefaultSettings.
]
{ #category : #'class initialization' }
CarpApplication class >> startUp: resuming [
resuming ifTrue: [ self stop ]
]
{ #category : #accessing }
CarpApplication >> baseApplication [
^ CarpApplication

View File

@@ -0,0 +1,15 @@
Class {
#name : #CarpArray,
#superclass : #CarpSequence,
#category : #'Carp-IDE'
}
{ #category : #accessing }
CarpArray >> close [
^ ']'
]
{ #category : #accessing }
CarpArray >> open [
^ '['
]

View File

@@ -7,6 +7,31 @@ Class {
#category : #'Carp-IDE'
}
{ #category : #'instance creation' }
CarpBinding class >> def [
^ CarpStaticVariable new
]
{ #category : #'instance creation' }
CarpBinding class >> defdynamic [
^ CarpDynamicVariable new
]
{ #category : #'instance creation' }
CarpBinding class >> defmacro [
^ CarpMacro new
]
{ #category : #'instance creation' }
CarpBinding class >> defn [
^ CarpStaticFunction new
]
{ #category : #'instance creation' }
CarpBinding class >> defndynamic [
^ CarpDynamicFunction new
]
{ #category : #accessing }
CarpBinding >> bindingName [
^ self subclassResponsibility

View File

@@ -0,0 +1,28 @@
Class {
#name : #CarpCharacter,
#superclass : #CarpLiteral,
#instVars : [
'character'
],
#category : #'Carp-IDE'
}
{ #category : #'instance creation' }
CarpCharacter class >> character: aCharacter [
^ self new character: aCharacter
]
{ #category : #accessing }
CarpCharacter >> character [
^ character
]
{ #category : #accessing }
CarpCharacter >> character: aCharacter [
character := aCharacter
]
{ #category : #accessing }
CarpCharacter >> toCarp [
^ '\', self character
]

View File

@@ -3,3 +3,8 @@ Class {
#superclass : #CarpNumber,
#category : #'Carp-IDE'
}
{ #category : #accessing }
CarpDouble >> suffix [
^ ''
]

View File

@@ -12,6 +12,17 @@ CarpExpression >> asElement [
^ (GtCarpCoderModel code: self toCarp) asElement
]
{ #category : #accessing }
CarpExpression >> asElementWithModule: aModule [
| applicationStrategy |
applicationStrategy := LeCarpApplicationStrategy new.
^ (GtExpandableSourceCoderElement new
coderViewModel: ((GtCarpIDECoderModel code: self toCarp)
module: aModule;
carpLinkApplicationStrategy: applicationStrategy;
expression: self) asCoderViewModel) collapse
]
{ #category : #accessing }
CarpExpression >> documentation [
^ documentation ifNil: ['']
@@ -22,6 +33,24 @@ CarpExpression >> documentation: aString [
documentation := aString
]
{ #category : #accessing }
CarpExpression >> gtCoderFor: aView [
<gtView>
^ aView explicit
title: 'Code';
priority: 1;
stencil: [ self asElement ]
]
{ #category : #accessing }
CarpExpression >> gtTextFor: aView [
<gtView>
^ aView textEditor
title: 'String';
priority: 2;
text: [ self toCarp ]
]
{ #category : #converting }
CarpExpression >> toCarp [
^ self subclassResponsibility

View File

@@ -0,0 +1,15 @@
Class {
#name : #CarpList,
#superclass : #CarpSequence,
#category : #'Carp-IDE'
}
{ #category : #accessing }
CarpList >> close [
^ ')'
]
{ #category : #accessing }
CarpList >> open [
^ '('
]

15
src/Carp/CarpMap.class.st Normal file
View File

@@ -0,0 +1,15 @@
Class {
#name : #CarpMap,
#superclass : #CarpSequence,
#category : #'Carp-IDE'
}
{ #category : #accessing }
CarpMap >> close [
^ '}'
]
{ #category : #accessing }
CarpMap >> open [
^ '{'
]

View File

@@ -67,8 +67,7 @@ CarpModule >> carpCoderCommentsFor: aView [
{ #category : #coders }
CarpModule >> carpCoderStreamingMethodsFor: aView context: aPhlowContext [
<gtModuleView>
| aMethodsCoder aMethodsCoderViewModel aNewMethodCoderHolder |
| aMethodsCoder aMethodsCoderViewModel aNewMethodCoderHolder coderElement |
aNewMethodCoderHolder := ValueHolder new.
^ aView explicit
@@ -76,46 +75,36 @@ CarpModule >> carpCoderStreamingMethodsFor: aView context: aPhlowContext [
title: 'Methods';
disableAsync;
actionDropdownButtonDo: [ :aDrodownAction |
aDrodownAction dropdown
aDrodownAction dropdown
icon: BrGlamorousVectorIcons add;
tooltip: 'Add new expression';
content: [ :aButton |
tooltip: 'Add new function';
content: [ :aButton |
| aNewMethodCoder aNewMethodCoderViewModel aHandler |
aNewMethodCoderHolder contents
ifNotNil: [ :aContents |
aNewMethodCoderViewModel := aContents ]
ifNil: [
aNewMethodCoder := GtCarpCoderModel new.
ifNotNil: [ :aContents | aNewMethodCoderViewModel := aContents ]
ifNil: [ aNewMethodCoder := GtCarpNewFunctionCoderModel new
module: self;
carpLinkApplicationStrategy: LeCarpApplicationStrategy new;
onSave: [ aButton fireEvent: BrDropdownHideWish new.
coderElement initializeForModule ].
aNewMethodCoderViewModel := aNewMethodCoder asCoderViewModel.
aNewMethodCoderViewModel
withoutHeader;
expanded: true;
focused: true;
moveCursorAtEnd.
aNewMethodCoderHolder contents: aNewMethodCoderViewModel.
aNewMethodCoderViewModel := aNewMethodCoder asCoderViewModel.
aNewMethodCoderViewModel
withoutHeader;
expanded: true;
focused: true;
moveCursorAtEnd.
aHandler := GtPharoNewMethodCodeSavedHandler new
methodsCoderViewModel: aMethodsCoderViewModel;
element: aButton;
methodCoderHolder: aNewMethodCoderHolder.
aNewMethodCoderViewModel weak
when: GtMethodCoderSaved
send: #onAnnouncement:
to: aHandler ].
aNewMethodCoderHolder contents: aNewMethodCoderViewModel ].
(GtExpandedOnlyCoderElement new coderViewModel: aNewMethodCoderViewModel)
hExact: 300;
vFitContent;
background: Color white;
padding: (BlInsets all: 5);
addAptitude: BrGlamorousFocusableShadowAptitude new ];
name: #'button--add-new-expression'];
stencil: [ CarpStreamingMethodsCoderElement forModule: self ]
(GtExpandedOnlyCoderElement new coderViewModel: aNewMethodCoderViewModel)
hExact: 300;
vFitContent;
background: Color white;
padding: (BlInsets all: 5);
addAptitude: BrGlamorousFocusableShadowAptitude new ];
name: #'button--add-new-expression' ];
stencil: [ coderElement := CarpStreamingMethodsCoderElement forModule: self ]
]
{ #category : #coders }
@@ -194,6 +183,11 @@ CarpModule >> name: aString [
name := aString
]
{ #category : #accessing }
CarpModule >> removeExpression: anExpression [
expressions remove: anExpression
]
{ #category : #accessing }
CarpModule >> removeUse: aString [
uses remove: aString

View File

@@ -19,6 +19,15 @@ CarpModuleCoder >> asCoderViewModel [
^ CarpModuleCoderViewModel new coder: self
]
{ #category : #accessing }
CarpModuleCoder >> coderName [
"Return a short textual name of the coder.
For example, class coder would return a class name, package coder returns a package name."
<return: #String>
^ self module name
]
{ #category : #'instance creation' }
CarpModuleCoder >> module [
^ module

View File

@@ -12,6 +12,17 @@ Class {
#category : #'Carp-Coder'
}
{ #category : #accessing }
CarpModuleCoderElement >> build [
| application commandFactory |
application := CarpApplication start.
commandFactory := application newCommandFactory.
^ commandFactory
<< self module toCarp;
sendAndWait
]
{ #category : #accessing }
CarpModuleCoderElement >> buildContentPane [
@@ -91,6 +102,13 @@ CarpModuleCoderElement >> buildModuleLabel [
action: [ :aButton |
aButton phlow spawnObject: self module toCarp ]).
aContainer addChild: (BrButton new
aptitude: BrGlamorousButtonWithIconAptitude;
icon: BrGlamorousVectorIcons refresh;
beSmallSize;
label: 'Build';
action: [ self build ]).
^ aContainer
]
@@ -133,7 +151,8 @@ CarpModuleCoderElement >> coderViewModel: aCarpCoderViewModel [
container ifNotNil: #removeFromParent.
container := self buildContentPane.
self addChildFirst: container
self addChildFirst: container.
self build
]
{ #category : #accessing }

View File

@@ -49,5 +49,5 @@ CarpNamedFunction >> toCarp [
aStream << '(' << self bindingName << ' ' << self name toCarp
<< ' ['.
arguments do: [ :anArgument | aStream << anArgument toCarp << ' ' ].
aStream << '] ' << self body toCarp << ')' ]
aStream ensureNoSpace << '] ' << self body toCarp << ')' ]
]

View File

@@ -0,0 +1,10 @@
Class {
#name : #CarpPattern,
#superclass : #CarpStringExpression,
#category : #'Carp-IDE'
}
{ #category : #accessing }
CarpPattern >> toCarp [
^ '#', super toCarp
]

View File

@@ -9,6 +9,12 @@ CarpPythonProcess class >> program [
^ 'python'
]
{ #category : #accessing }
CarpPythonProcess class >> resolveCarpPath [
"TODO: make more robust"
^ '/usr/bin/python' asFileReference
]
{ #category : #accessing }
CarpPythonProcess >> processArguments [
| args |

View File

@@ -0,0 +1,43 @@
Class {
#name : #CarpSequence,
#superclass : #CarpLiteral,
#instVars : [
'elements',
'contents'
],
#category : #'Carp-IDE'
}
{ #category : #'instance creation' }
CarpSequence class >> contents: aCollection [
^ self new contents: aCollection
]
{ #category : #accessing }
CarpSequence >> close [
^ self subclassResponsibility
]
{ #category : #accessing }
CarpSequence >> contents: aCollection [
contents := aCollection
]
{ #category : #accessing }
CarpSequence >> do: aBlock [
contents do: aBlock
]
{ #category : #accessing }
CarpSequence >> open [
^ self subclassResponsibility
]
{ #category : #accessing }
CarpSequence >> toCarp [
^ String streamContents: [ :aStream |
aStream << self open.
contents do: [ :anArgument | aStream << anArgument toCarp << ' ' ].
aStream ensureNoSpace << self close]
]

View File

@@ -26,7 +26,7 @@ CarpStreamingMethodsCoderElement >> initialize [
itemType: [ :anItemTypeFactory :anItemObject |
anItemObject ];
itemStencil: [ :anItem |
anItem asElement id: GtSourceCoderId ];
(anItem asElementWithModule: module) id: GtSourceCoderId ];
itemsProvider:
(BrListStreamItemsProvider new stream: AsyncEmptyStream new).

View File

@@ -12,6 +12,11 @@ CarpSymbol class >> named: aString [
^ self new name: aString
]
{ #category : #accessing }
CarpSymbol >> name [
^ name
]
{ #category : #accessing }
CarpSymbol >> name: aString [
name := aString

View File

@@ -33,7 +33,9 @@ GtCarpCoderModel >> bindAndExecute: sourceString [
| res trimmedSource ast varNames lastStatement carpSource |
trimmedSource := SmaCCString on: sourceString trimRight.
ast := CarpParser parse: trimmedSource. "The variables to be returned are names that are in pharoBindings"
varNames := pharoBindings bindingNames asSet. "Assign the final statement to snippetResult"
varNames := pharoBindings
ifNil: [ Set new ]
ifNotNil: [ pharoBindings bindingNames asSet ]. "Assign the final statement to snippetResult"
lastStatement := ast expressions last.
trimmedSource
insert: '(defdynamic snippetResult '
@@ -46,10 +48,10 @@ GtCarpCoderModel >> bindAndExecute: sourceString [
res := self bindAndExecuteRaw: sourceString.
(res at: #result) = 'success' ifTrue: [ ^ CarpExecutionResult from: res ].
exception := (PharoLinkRemoteError new
application: application;
command: commandFactory command;
trace: (res at: #value)).
exception := PharoLinkRemoteError new
application: application;
command: commandFactory command;
trace: (res at: #value).
exception signal
]
@@ -87,56 +89,58 @@ GtCarpCoderModel >> initializeAddOns: addOns [
addOns
addStyler: (GtCoderAstSmaCCParserStyler new smaccStyler: CarpParser gtStyler).
addOns
addMainAction: 'Evaluate' translated
icon: BrGlamorousVectorIcons play
action: [ :aCoderUIModel :anElement |
GtCoderCodeExecutor doIt
coderViewModel: aCoderUIModel;
element: anElement;
execute ]
id: GtSourceCoderDoItActionId.
addOns
addMainAction: 'Inspect' translated
icon: BrGlamorousVectorIcons playinspect
action: [ :aCoderUIModel :anElement |
GtCoderCodeExecutor doItAndGo
coderViewModel: aCoderUIModel;
element: anElement;
execute ]
id: GtSourceCoderDoItAndGoActionId.
addOns
addMainAction: 'Expand Macros' translated
icon: BrGlamorousVectorIcons repair
action: [ :aCoderUIModel :anElement |
| source |
source := '(expand ''' , sourceCode currentSourceText value text , ')'.
anElement phlow
spawnObject: ((self bindAndExecute: source) parse view: #gtSourceFor:) ]
id: #'source-coder--macro-expand-action'.
addOns
addMainAction: 'Build and Run' translated
icon: BrGlamorousVectorIcons refresh
action: [ :aCoderUIModel :anElement |
| source |
source := '' , sourceCode currentSourceText value text , '(build) (run)'.
anElement phlow
spawnObject: (CarpCliOutput text: ((self bindAndExecuteRaw: source) at: 'value')) ]
id: #'source-coder--build-and-run-action'.
addOns
addMainAction: 'Infer Type' translated
icon: BrGlamorousVectorIcons inspect
action: [ :aCoderUIModel :anElement | self inspectTypeSpawningOn: anElement phlow]
id: #'source-coder--type-infer-action'
application
ifNotNil: [ addOns
addMainAction: 'Evaluate' translated
icon: BrGlamorousVectorIcons play
action: [ :aCoderUIModel :anElement |
GtCoderCodeExecutor doIt
coderViewModel: aCoderUIModel;
element: anElement;
execute ]
id: GtSourceCoderDoItActionId.
addOns
addMainAction: 'Inspect' translated
icon: BrGlamorousVectorIcons playinspect
action: [ :aCoderUIModel :anElement |
GtCoderCodeExecutor doItAndGo
coderViewModel: aCoderUIModel;
element: anElement;
execute ]
id: GtSourceCoderDoItAndGoActionId.
addOns
addMainAction: 'Expand Macros' translated
icon: BrGlamorousVectorIcons repair
action: [ :aCoderUIModel :anElement |
| source |
source := '(expand ''' , sourceCode currentSourceText value text , ')'.
anElement phlow
spawnObject: ((self bindAndExecute: source) parse view: #gtSourceFor:) ]
id: #'source-coder--macro-expand-action'.
addOns
addMainAction: 'Build and Run' translated
icon: BrGlamorousVectorIcons refresh
action: [ :aCoderUIModel :anElement |
| source |
source := '' , sourceCode currentSourceText value text , '(build) (run)'.
anElement phlow
spawnObject: (CarpCliOutput text: ((self bindAndExecuteRaw: source) at: 'value')) ]
id: #'source-coder--build-and-run-action'.
addOns
addMainAction: 'Infer Type' translated
icon: BrGlamorousVectorIcons inspect
action: [ :aCoderUIModel :anElement | self inspectTypeSpawningOn: anElement phlow ]
id: #'source-coder--type-infer-action' ]
]
{ #category : #accessing }
GtCarpCoderModel >> initializeShortcuts: addOns [
super initializeShortcuts: addOns.
addOns
addShortcut: GtSourceCoderDoItShortcut new;
addShortcut: GtSourceCoderDoItAndInspectShortcut new
application
ifNotNil: [ addOns
addShortcut: GtSourceCoderDoItShortcut new;
addShortcut: GtSourceCoderDoItAndInspectShortcut new ]
]
{ #category : #accessing }

View File

@@ -0,0 +1,50 @@
Class {
#name : #GtCarpIDECoderModel,
#superclass : #GtCarpNewFunctionCoderModel,
#instVars : [
'expression'
],
#category : #'Carp-Coder'
}
{ #category : #accessing }
GtCarpIDECoderModel >> collapsedTextPromise [
^ self expression name name , ' : '
, (self bindAndExecute: '(type ' , module name, '.', self expression name name , ')') value
]
{ #category : #accessing }
GtCarpIDECoderModel >> expression [
^ expression
]
{ #category : #accessing }
GtCarpIDECoderModel >> expression: anExpression [
expression := anExpression
]
{ #category : #accessing }
GtCarpIDECoderModel >> initializeAddOns: addOns [
super initializeAddOns: addOns.
addOns
addMainAction: 'Remove' translated
icon: BrGlamorousVectorIcons remove
action: [ :aCoderUIModel :anElement | self remove ]
id: GtMethodCoderSaveActionId
]
{ #category : #accessing }
GtCarpIDECoderModel >> remove [
module removeExpression: self expression.
self bindAndExecute: module toCarp
]
{ #category : #accessing }
GtCarpIDECoderModel >> save [
module removeExpression: expression.
module
addExpression: (CarpParser parse: sourceCode availableSource text) intoModel.
self bindAndExecute: module toCarp.
onSave ifNotNil: [ onSave value ]
]

View File

@@ -0,0 +1,40 @@
Class {
#name : #GtCarpNewFunctionCoderModel,
#superclass : #GtCarpCoderModel,
#instVars : [
'module',
'onSave'
],
#category : #'Carp-Coder'
}
{ #category : #accessing }
GtCarpNewFunctionCoderModel >> initializeAddOns: addOns [
addOns
addStyler: (GtCoderAstSmaCCParserStyler new smaccStyler: CarpParser gtStyler).
addOns
addMainAction: 'Save' translated
icon: BrGlamorousVectorIcons accept
action: [ :aCoderUIModel :anElement | self save ]
id: GtMethodCoderSaveActionId
]
{ #category : #coders }
GtCarpNewFunctionCoderModel >> module: aModule [
module := aModule
]
{ #category : #accessing }
GtCarpNewFunctionCoderModel >> onSave: aBlock [
onSave := aBlock
]
{ #category : #accessing }
GtCarpNewFunctionCoderModel >> save [
| expression |
expression := (CarpParser parse: sourceCode currentSourceText value text) intoModel.
module addExpression: expression.
self bindAndExecute: module toCarp.
onSave ifNotNil: [ onSave value ]
]

View File

@@ -13,9 +13,6 @@ LeCarpApplicationStrategy class >> strategyName [
{ #category : #accessing }
LeCarpApplicationStrategy >> applicationServer [
content database isDatabase ifFalse: [ ^ nil ].
CarpApplication uniqueInstance ifNil:
[ CarpApplication uniqueInstance: (self newCarpApplicationFor: content database) ].
^ CarpApplication uniqueInstance
]
@@ -27,32 +24,5 @@ LeCarpApplicationStrategy >> applicationSettings [
^ CarpApplication isRunning ifTrue:
[ CarpApplication uniqueInstance settings ]
ifFalse:
[ self updatedSettings: CarpApplication defaultSettings ]
]
{ #category : #accessing }
LeCarpApplicationStrategy >> newCarpApplicationFor: aLeDatabase [
^ CarpApplication new initializeWith:
(self updatedSettings: LanguageLinkSettings carpDefaultSettings).
]
{ #category : #accessing }
LeCarpApplicationStrategy >> updatedSettings: applicationCarpSettings [
"Update the supplied settings with the lepiter configuration"
| lepiterCarpSettings lepiterDatabase carpDir |
lepiterDatabase := content database.
(lepiterDatabase isKindOf: LeNullDatabase)
ifTrue: [ ^ applicationCarpSettings ].
lepiterCarpSettings := lepiterDatabase properties carpLinkSettings.
lepiterCarpSettings directory
ifNotNil: [ :relativeDir |
carpDir := lepiterDatabase localStoreRootDirectory resolve: relativeDir.
applicationCarpSettings workingDirectory: carpDir ]. "lepiterCarpSettings carpPath ifNotNil:
[ :carpPath | applicationCarpSettings serverExecutable: carpPath ]."
applicationCarpSettings serverDebugMode: lepiterCarpSettings serverDebugMode.
^ applicationCarpSettings
[ CarpApplication defaultSettings ]
]

View File

@@ -1,11 +1,11 @@
Extension { #name : #ByteString }
Extension { #name : #String }
{ #category : #'*Carp' }
ByteString >> asCarpModule [
String >> asCarpModule [
^ CarpModule named: self
]
{ #category : #'*Carp' }
ByteString >> asCarpSymbol [
String >> asCarpSymbol [
^ CarpSymbol named: self
]