Skip to content

Commit

Permalink
backup before major cleanup
Browse files Browse the repository at this point in the history
  • Loading branch information
Dierk Koenig committed Aug 20, 2015
1 parent 27bb614 commit ca549ed
Show file tree
Hide file tree
Showing 32 changed files with 16,491 additions and 1,770 deletions.
2 changes: 1 addition & 1 deletion Stairs.fr
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Stairs where

import org.frege.SketchBook
import fregefx.javafx.scene.canvas.GraphicsContext
import fregefx.JavaFxAll (GraphicsContext)
import Data.List

--- A point on the canvas.
Expand Down
36 changes: 10 additions & 26 deletions client/src/main/frege/org/frege/Application.fr
Original file line number Diff line number Diff line change
Expand Up @@ -11,25 +11,7 @@ import Data.List
import org.frege.JavaFX
import org.frege.AllNodes

import fregefx.javafx.application.Platform
import fregefx.javafx.fxml.FXMLLoader
import fregefx.javafx.stage.Stage
import fregefx.javafx.scene.Scene
import fregefx.javafx.scene.Node
import fregefx.javafx.scene.Parent
import fregefx.javafx.event.Event
import fregefx.javafx.scene.input.KeyEvent
import fregefx.javafx.scene.input.KeyCode
import fregefx.javafx.scene.text.Font
import fregefx.javafx.scene.control.Button
import fregefx.javafx.scene.control.TextArea
import fregefx.javafx.scene.control.TextInputControl
import fregefx.javafx.stage.WindowEvent
import fregefx.javafx.event.EventHandler
import fregefx.javafx.collections.ObservableList

import fregefx.javafx.scene.web.WebView
import fregefx.javafx.scene.web.WebEngine
import fregefx.JavaFxAll hiding (Method)

main args = do
mConsole <- MVar.newEmpty -- for thread coordination, set in showUI thread, start repl when ready
Expand All @@ -45,9 +27,9 @@ showUI mConsole stage = do
stage.setTitle "Frege - purely functional programming for the JVM"
stage.setScene scene
Stage.show stage
inputArea <- locateTextArea scene "#editor"
outputArea <- locateTextArea scene "#repl"
historyLV <- locateListView scene "#historyList"
inputArea <- lookupNode scene "#editor"
outputArea <- lookupNode scene "#repl"
historyLV <- lookupNode scene "#historyList" :: IO (ListView String)

items <- historyLV.getItems
items.add ":help mapM"
Expand Down Expand Up @@ -115,7 +97,8 @@ onKeyReleased mQueue stage inputArea outputArea items historySelection = OnEvent
code <- keyEvent.getCode
-- println . show $ code.getName
keyEvent.consume
case code.getName of
codeName <- code.getName
case codeName of
"Down" -> selectNext items historySelection
"Up" -> selectPrevious items historySelection
"Enter" -> doExecute mQueue inputArea items historySelection
Expand All @@ -138,14 +121,15 @@ doExecute mQueue inputArea items historySelection = do
then [trim script]
else [":{"] ++ lines script ++ [":}"]
mapM mQueue.put scriptLines -- the beef
items.remove $ trim script
List.remove items $ trim script
items.add $ trim script
historySelection.clearSelection
inputArea.setText ""
when (script == ":q") $ System.exit 0

loadFile :: Stage -> TextArea -> IO ()
loadFile stage inputArea = do
return ()
chooser <- FileChooser.new ()
chooser.setTitle "Load Frege File"
maybeFile <- chooser.showOpenDialog stage
Expand Down Expand Up @@ -236,8 +220,8 @@ monolog title content =
withUI do
webView <- WebView.new ()
webView.getEngine >>= _.loadContent content
scene <- Scene.new webView 600.0 600.0
stage <- Stage.new ()
scene <- Scene.new webView 600d 600d :: IO Scene
stage <- Stage.new () :: IO Stage
stage.setTitle title
stage.setScene scene
stage.show
Expand Down
5 changes: 5 additions & 0 deletions client/src/main/frege/org/frege/Hello.fr
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
module org.frege.Hello where


main _ = do
println "Hello"
22 changes: 10 additions & 12 deletions client/src/main/frege/org/frege/SketchBook.fr
Original file line number Diff line number Diff line change
Expand Up @@ -11,12 +11,9 @@

module org.frege.SketchBook where

import fregefx.javafx.application.Platform
import fregefx.javafx.scene.canvas.GraphicsContext
import fregefx.javafx.scene.canvas.Canvas
import fregefx.javafx.scene.Group
import fregefx.javafx.stage.Stage
import fregefx.javafx.scene.Scene
import fregefx.JavaFxAll (Platform, GraphicsContext, Canvas, Group, Stage, Scene)

import org.frege.AllNodes

import Control.Concurrent

Expand All @@ -34,22 +31,23 @@ paint draw = do
withUI :: IO () -> IO ()
withUI f = Platform.runLater =<< Runnable.new f


--- Make a frame (stage) with a canvas of the given _width_ and _height_.
--- Set the graphicsContext into the _ctxHolder_ once it is available such that other threads that wait for it can proceed.
--- The (0,0) origin is centered and y coordinates point upwards like it is conventional in mathematics.
canvas :: Double -> Double -> MVar GraphicsContext -> IO ()
canvas width height ctxHolder = withUI do -- UI construction must happen inside the UI thread
grp <- Group.new ()
grp <- Group.new () :: IO Group
kids <- grp.getChildren
canvas <- Canvas.new width height
canvas <- Canvas.new width height :: IO Canvas
ctx <- canvas.getGraphicsContext2D
kids.add canvas
scene <- Scene.new grp width height
stage <- Stage.new ()
scene <- Scene.new grp width height :: IO Scene
stage <- Stage.new () :: IO Stage
stage.setScene scene
stage.show
ctx.translate (width / 2) (height / 2) -- center 0,0
ctx.scale 1 (-1) -- mirror y axis
ctx.translate (width / 2d) (height / 2d) -- center 0,0
ctx.scale 1d (-1d) -- mirror y axis
ctxHolder.put ctx

--- Example on how to use the sketchbook API that draws a crosshair.
Expand Down
64 changes: 31 additions & 33 deletions fregeFX/src/main/frege/org/frege/JavaFX.fr
Original file line number Diff line number Diff line change
Expand Up @@ -2,40 +2,38 @@ module org.frege.JavaFX where

import frege.Prelude hiding(ListView)

import fregefx.JavaFxAll
import org.frege.AllNodes
import fregefx.javafx.scene.Node
import fregefx.javafx.scene.Scene
import fregefx.javafx.scene.control.TextArea


data Classifier = mutable native org.frege.Classifier where
native classify org.frege.Classifier.classify :: Node -> IO (IllegalArgumentException | AllNodes t)

locateTextArea :: Scene -> String -> IO TextArea
locateTextArea scene selector = do
allNode <- locate scene selector
case allNode of
TextArea ta -> return ta
_ -> error ("Node " ++ selector ++ " is not a TextArea")

locateListView :: Scene -> String -> IO (ListView t)
locateListView scene selector = do
allNode <- locate scene selector
case allNode of
ListView lv -> return lv
_ -> error ("Node " ++ selector ++ " is not a ListView")


locate :: Scene -> String -> IO (AllNodes t)
locate scene selector = do
maybeNode <- Scene.lookup scene selector
case maybeNode of
Nothing -> error $ "Sorry, could not find any node for '" ++ selector ++"'."
Just allNode -> do
classified <- Classifier.classify allNode
case classified of
Left ex -> error $ "Unknown node type located for '" ++ selector ++ "'."
Right x -> return x


--data Classifier = mutable native org.frege.Classifier where
-- native classify org.frege.Classifier.classify :: Node -> IO (IllegalArgumentException | AllNodes t)
--
--locateTextArea :: Scene -> String -> IO TextArea
--locateTextArea scene selector = do
-- allNode <- locate scene selector
-- case allNode of
-- TextArea ta -> return ta
-- _ -> error ("Node " ++ selector ++ " is not a TextArea")
--
--locateListView :: Scene -> String -> IO (ListView t)
--locateListView scene selector = do
-- allNode <- locate scene selector
-- case allNode of
-- ListView lv -> return lv
-- _ -> error ("Node " ++ selector ++ " is not a ListView")
--
--
--locate :: Scene -> String -> IO (AllNodes t)
--locate scene selector = do
-- maybeNode <- Scene.lookup scene selector
-- case maybeNode of
-- Nothing -> error $ "Sorry, could not find any node for '" ++ selector ++"'."
-- Just allNode -> do
-- classified <- Classifier.classify allNode
-- case classified of
-- Left ex -> error $ "Unknown node type located for '" ++ selector ++ "'."
-- Right x -> return x



Expand Down
14 changes: 7 additions & 7 deletions fregeFX/src/main/java/org/frege/Classifier.java
Original file line number Diff line number Diff line change
Expand Up @@ -7,11 +7,11 @@

public class Classifier {

static public org.frege.AllNodes.TAllNodes classify(Node n) throws IllegalArgumentException {
if (n instanceof Button) return org.frege.AllNodes.TAllNodes.DButton.mk((Button) n);
if (n instanceof TextArea) return org.frege.AllNodes.TAllNodes.DTextArea.mk((TextArea) n);
if (n instanceof ListView) return org.frege.AllNodes.TAllNodes.DListView.mk((ListView) n);
System.out.println("Cannot cast node " + n.getClass() + " to a known type");
throw new IllegalArgumentException("Cannot cast node " + n.getClass() + " to a known type");
}
// static public org.frege.AllNodes.TAllNodes classify(Node n) throws IllegalArgumentException {
// if (n instanceof Button) return org.frege.AllNodes.TAllNodes.DButton.mk((Button) n);
// if (n instanceof TextArea) return org.frege.AllNodes.TAllNodes.DTextArea.mk((TextArea) n);
// if (n instanceof ListView) return org.frege.AllNodes.TAllNodes.DListView.mk((ListView) n);
// System.out.println("Cannot cast node " + n.getClass() + " to a known type");
// throw new IllegalArgumentException("Cannot cast node " + n.getClass() + " to a known type");
// }
}
Loading

0 comments on commit ca549ed

Please sign in to comment.