2016-01-05 04:18:42 +03:00
|
|
|
{-# LANGUAGE NoMonomorphismRestriction, FlexibleContexts, TypeFamilies #-}
|
|
|
|
module Main where
|
|
|
|
|
|
|
|
import Diagrams.Prelude
|
|
|
|
import Diagrams.Backend.SVG.CmdLine
|
2016-01-08 04:03:04 +03:00
|
|
|
|
2016-01-27 02:29:02 +03:00
|
|
|
import Icons(apply0NDia, colorScheme, ColorStyle(..))
|
2016-01-23 05:28:55 +03:00
|
|
|
import Rendering(renderDrawing)
|
|
|
|
import Util(toNames, portToPort, iconToPort, iconToIcon,
|
2016-01-27 02:29:02 +03:00
|
|
|
iconToIconEnds, iconTailToPort)
|
2016-01-21 05:24:42 +03:00
|
|
|
import Types(Icon(..), Drawing(..), EdgeEnd(..))
|
2016-02-04 11:19:08 +03:00
|
|
|
import Translate(translateString)
|
2016-01-05 04:18:42 +03:00
|
|
|
|
2016-01-21 05:24:42 +03:00
|
|
|
-- TODO Now --
|
2016-02-18 10:14:14 +03:00
|
|
|
-- Refactor evalApp to use combineExpressions
|
2016-01-21 05:24:42 +03:00
|
|
|
|
|
|
|
-- TODO Later --
|
2016-02-10 09:29:07 +03:00
|
|
|
-- Eliminate BranchIcon for the identity funciton "y x = x"
|
2016-02-10 05:58:28 +03:00
|
|
|
-- Let lines connect to ports in multiple locations (eg. argument for Apply0Dia)
|
2016-01-22 00:35:34 +03:00
|
|
|
-- Add a small black border to lines to help distinguish line crossings.
|
2016-01-10 06:17:22 +03:00
|
|
|
-- todo: Find out how to hide unqualified names such that recursive drawings are connected correctly
|
2016-01-20 02:52:56 +03:00
|
|
|
-- todo: Find out and fix why connectinos to sub-icons need to be qualified twice (eg. "lam0" .> "arg" .> "arg")
|
2016-01-19 14:08:53 +03:00
|
|
|
-- todo: Rotate based on difference from ideal tangent angle, not line distance.
|
2016-01-23 05:28:55 +03:00
|
|
|
-- todo: Try using connectPerim for port to port connections. Hopefully this will draw a spline.
|
2016-01-19 14:08:53 +03:00
|
|
|
-- todo: layout and rotate considering external connections.
|
2016-01-21 05:24:42 +03:00
|
|
|
|
2016-01-22 12:38:28 +03:00
|
|
|
(d0A, d0B, d0Res, d0Foo, d0Bar) = ("A", "B", "res", "foo", "bar")
|
2016-01-09 06:54:07 +03:00
|
|
|
d0Icons = toNames
|
2016-02-10 10:50:38 +03:00
|
|
|
[(d0A, Apply0NIcon 1),
|
|
|
|
(d0B, Apply0NIcon 1),
|
2016-01-22 12:38:28 +03:00
|
|
|
(d0Res, ResultIcon),
|
|
|
|
(d0Foo, TextBoxIcon d0Foo),
|
|
|
|
(d0Bar, TextBoxIcon d0Bar)
|
2016-01-09 04:53:12 +03:00
|
|
|
]
|
2016-01-08 04:03:04 +03:00
|
|
|
|
2016-01-09 06:54:07 +03:00
|
|
|
d0Edges =
|
2016-01-08 13:15:37 +03:00
|
|
|
[
|
2016-02-10 10:50:38 +03:00
|
|
|
portToPort d0A 0 d0B 1,
|
2016-01-22 12:38:28 +03:00
|
|
|
iconToPort d0Foo d0B 0,
|
2016-02-10 10:50:38 +03:00
|
|
|
iconToPort d0Res d0A 1,
|
2016-01-22 12:38:28 +03:00
|
|
|
iconToPort d0Foo d0B 0,
|
2016-02-10 10:50:38 +03:00
|
|
|
iconToPort d0Bar d0B 2,
|
|
|
|
iconToPort d0Bar d0A 2
|
2016-01-08 13:15:37 +03:00
|
|
|
]
|
2016-01-08 04:03:04 +03:00
|
|
|
|
2016-01-10 06:17:22 +03:00
|
|
|
drawing0 = Drawing d0Icons d0Edges []
|
|
|
|
d0Name = toName "d0"
|
|
|
|
|
2016-01-22 12:38:28 +03:00
|
|
|
(s1Lam, s1y, s1z, s1q) = ("lam0", "y", "z", "q")
|
|
|
|
superIcons = toNames [
|
|
|
|
(s1Lam, LambdaRegionIcon 3 d0Name),
|
|
|
|
(s1y, TextBoxIcon s1y),
|
|
|
|
(s1z, TextBoxIcon s1z),
|
|
|
|
(s1q, TextBoxIcon s1q)
|
2016-01-09 04:53:12 +03:00
|
|
|
]
|
|
|
|
|
2016-01-22 12:38:28 +03:00
|
|
|
superEdges =
|
|
|
|
[
|
|
|
|
portToPort (s1Lam .> d0A) 1 s1Lam 0,
|
|
|
|
iconToIcon s1y s1Lam,
|
|
|
|
iconToIcon s1z s1Lam,
|
|
|
|
iconToIcon s1q s1Lam,
|
|
|
|
iconToIcon d0A s1z,
|
|
|
|
iconToPort (s1Lam .> d0Foo .> d0Foo) s1Lam 0
|
2016-01-09 04:53:12 +03:00
|
|
|
]
|
|
|
|
|
|
|
|
--superDrawing = Drawing [((toName "lam0"), LambdaRegionIcon 3 (toName"d0"))] superEdges [((toName "d0"), drawing0)]
|
2016-01-09 06:54:07 +03:00
|
|
|
superDrawing = Drawing superIcons superEdges [(d0Name, drawing0)]
|
2016-01-08 13:15:37 +03:00
|
|
|
|
2016-01-10 06:17:22 +03:00
|
|
|
super2Icons = toNames [
|
2016-01-22 12:38:28 +03:00
|
|
|
(s1Lam, LambdaRegionIcon 1 d0Name),
|
2016-01-10 06:17:22 +03:00
|
|
|
--("y", TextBoxIcon "y"),
|
|
|
|
("lam1", LambdaRegionIcon 2 d0Name)
|
|
|
|
]
|
|
|
|
|
|
|
|
super2Edges =
|
|
|
|
[
|
2016-01-22 12:38:28 +03:00
|
|
|
iconToIcon s1Lam "lam1"
|
2016-01-10 06:17:22 +03:00
|
|
|
--iconToIcon "y" "lam0"
|
|
|
|
]
|
|
|
|
|
|
|
|
super2Drawing = Drawing super2Icons super2Edges [(d0Name, drawing0)]
|
|
|
|
super2Name = toName "s2"
|
|
|
|
|
|
|
|
super3Icons = toNames [
|
2016-01-22 12:38:28 +03:00
|
|
|
(s1Lam, LambdaRegionIcon 3 super2Name),
|
2016-01-10 06:17:22 +03:00
|
|
|
--("y", TextBoxIcon "y"),
|
2016-01-22 12:38:28 +03:00
|
|
|
("lam1", LambdaRegionIcon 4 super2Name)
|
2016-01-10 06:17:22 +03:00
|
|
|
]
|
|
|
|
|
|
|
|
super3Edges =
|
|
|
|
[
|
|
|
|
-- iconToIcon "lam0" "lam1",
|
2016-01-22 12:38:28 +03:00
|
|
|
iconToIcon s1Lam "A"
|
2016-01-10 06:17:22 +03:00
|
|
|
]
|
2016-01-22 12:38:28 +03:00
|
|
|
|
|
|
|
super3Drawing = Drawing super3Icons super2Edges [(super2Name, super2Drawing)]
|
|
|
|
|
|
|
|
(fG0, fOne, fEq0, fMinus1, fEq0Ap, fMinus1Ap, fTimes, fRecurAp, fTimesAp, fArg, fRes) =
|
|
|
|
("g0", "one", "eq0", "-1", "eq0Ap", "-1Ap", "*", "recurAp", "*Ap", "arg", "res")
|
2016-01-10 06:17:22 +03:00
|
|
|
|
2016-01-20 02:52:56 +03:00
|
|
|
fact0Icons = toNames
|
2016-01-14 02:08:08 +03:00
|
|
|
[
|
2016-01-22 12:38:28 +03:00
|
|
|
(fG0, GuardIcon 2),
|
|
|
|
(fOne, TextBoxIcon "1"),
|
|
|
|
(fEq0, TextBoxIcon "== 0"),
|
|
|
|
(fMinus1, TextBoxIcon fMinus1),
|
2016-02-10 10:50:38 +03:00
|
|
|
(fEq0Ap, Apply0NIcon 1),
|
|
|
|
(fMinus1Ap, Apply0NIcon 1),
|
2016-01-22 12:38:28 +03:00
|
|
|
(fTimes, TextBoxIcon fTimes),
|
2016-02-10 10:50:38 +03:00
|
|
|
(fRecurAp, Apply0NIcon 1),
|
2016-01-22 12:38:28 +03:00
|
|
|
(fTimesAp, Apply0NIcon 2),
|
|
|
|
(fArg, BranchIcon),
|
|
|
|
(fRes, ResultIcon)
|
2016-01-14 02:08:08 +03:00
|
|
|
]
|
|
|
|
|
2016-01-20 02:52:56 +03:00
|
|
|
fact0Edges = [
|
2016-01-22 12:38:28 +03:00
|
|
|
iconToPort fEq0 fEq0Ap 0,
|
2016-02-10 10:50:38 +03:00
|
|
|
portToPort fEq0Ap 1 fG0 3,
|
2016-01-22 12:38:28 +03:00
|
|
|
iconToPort fMinus1 fMinus1Ap 0,
|
|
|
|
iconToPort fTimes fTimesAp 0,
|
|
|
|
iconToPort fOne fG0 2,
|
2016-02-10 10:50:38 +03:00
|
|
|
portToPort fTimesAp 2 fG0 4,
|
|
|
|
portToPort fRecurAp 1 fTimesAp 3,
|
|
|
|
iconToPort fArg fEq0Ap 2,
|
|
|
|
iconToPort fArg fMinus1Ap 2,
|
|
|
|
iconToPort fArg fTimesAp 1,
|
|
|
|
portToPort fMinus1Ap 1 fRecurAp 2,
|
2016-01-22 12:38:28 +03:00
|
|
|
iconToPort fRes fG0 0
|
2016-01-14 02:08:08 +03:00
|
|
|
]
|
|
|
|
|
2016-01-20 02:52:56 +03:00
|
|
|
fact0Drawing = Drawing fact0Icons fact0Edges []
|
|
|
|
fact0Name = toName "fac0"
|
|
|
|
|
|
|
|
factLam0Icons = toNames [
|
|
|
|
("lam0", LambdaRegionIcon 1 fact0Name),
|
|
|
|
("fac", TextBoxIcon "factorial")
|
|
|
|
]
|
|
|
|
|
|
|
|
factLam0Edges = [
|
2016-02-10 10:50:38 +03:00
|
|
|
iconToPort ("lam0" .> fArg) "lam0" 0,
|
2016-01-22 12:38:28 +03:00
|
|
|
iconToPort "lam0" ("lam0" .> fRecurAp) 0,
|
2016-01-20 02:52:56 +03:00
|
|
|
iconToIcon "lam0" "fac"
|
|
|
|
]
|
|
|
|
|
|
|
|
factLam0Drawing = Drawing factLam0Icons factLam0Edges [(fact0Name, fact0Drawing)]
|
2016-01-14 02:08:08 +03:00
|
|
|
|
2016-01-21 06:37:03 +03:00
|
|
|
fact1Icons = toNames
|
|
|
|
[
|
2016-01-22 12:38:28 +03:00
|
|
|
(fG0, GuardIcon 2),
|
|
|
|
(fOne, TextBoxIcon "1"),
|
|
|
|
(fEq0, TextBoxIcon "== 0"),
|
|
|
|
(fMinus1, TextBoxIcon fMinus1),
|
|
|
|
(fTimes, TextBoxIcon fTimes),
|
2016-02-10 10:50:38 +03:00
|
|
|
(fRecurAp, Apply0NIcon 1),
|
2016-01-22 12:38:28 +03:00
|
|
|
(fTimesAp, Apply0NIcon 2),
|
|
|
|
(fArg, BranchIcon),
|
|
|
|
(fRes, ResultIcon)
|
2016-01-21 06:37:03 +03:00
|
|
|
]
|
|
|
|
|
|
|
|
fact1Edges = [
|
2016-01-22 12:38:28 +03:00
|
|
|
iconToIconEnds fArg EndNone fEq0 EndAp1Arg,
|
|
|
|
iconTailToPort fEq0 EndAp1Result fG0 3,
|
|
|
|
iconToIconEnds fArg EndNone fMinus1 EndAp1Arg,
|
2016-02-10 10:50:38 +03:00
|
|
|
iconTailToPort fMinus1 EndAp1Result fRecurAp 2,
|
2016-01-22 12:38:28 +03:00
|
|
|
iconToPort fTimes fTimesAp 0,
|
|
|
|
iconToPort fOne fG0 2,
|
|
|
|
portToPort fTimesAp 1 fG0 4,
|
2016-02-10 10:50:38 +03:00
|
|
|
portToPort fRecurAp 1 fTimesAp 3,
|
2016-01-22 12:38:28 +03:00
|
|
|
iconToPort fArg fTimesAp 2,
|
|
|
|
iconToPort fRes fG0 0
|
2016-01-21 06:37:03 +03:00
|
|
|
]
|
|
|
|
|
|
|
|
fact1Drawing = Drawing fact1Icons fact1Edges []
|
|
|
|
|
|
|
|
factLam1Drawing = Drawing factLam0Icons factLam0Edges [(fact0Name, fact1Drawing)]
|
|
|
|
|
2016-01-23 05:08:53 +03:00
|
|
|
-- fact2 is like fact1, but uses fTimesAp port 2 to distrubute the argument,
|
|
|
|
-- not fArg
|
|
|
|
fact2Icons = toNames
|
|
|
|
[
|
|
|
|
(fG0, GuardIcon 2),
|
|
|
|
(fOne, TextBoxIcon "1"),
|
|
|
|
(fEq0, TextBoxIcon "== 0"),
|
|
|
|
(fMinus1, TextBoxIcon fMinus1),
|
|
|
|
(fTimes, TextBoxIcon fTimes),
|
2016-02-10 10:50:38 +03:00
|
|
|
(fRecurAp, Apply0NIcon 1),
|
2016-01-23 05:08:53 +03:00
|
|
|
(fTimesAp, Apply0NIcon 2),
|
|
|
|
--(fArg, BranchIcon),
|
|
|
|
(fRes, ResultIcon)
|
|
|
|
]
|
|
|
|
|
|
|
|
fact2Edges = [
|
|
|
|
--iconToIconEnds fArg EndNone fEq0 EndAp1Arg,
|
|
|
|
iconTailToPort fEq0 EndAp1Arg fTimesAp 2,
|
|
|
|
iconTailToPort fEq0 EndAp1Result fG0 3,
|
|
|
|
--iconToIconEnds fArg EndNone fMinus1 EndAp1Arg,
|
|
|
|
iconTailToPort fMinus1 EndAp1Arg fTimesAp 2,
|
2016-02-10 10:50:38 +03:00
|
|
|
iconTailToPort fMinus1 EndAp1Result fRecurAp 2,
|
2016-01-23 05:08:53 +03:00
|
|
|
iconToPort fTimes fTimesAp 0,
|
|
|
|
iconToPort fOne fG0 2,
|
|
|
|
portToPort fTimesAp 1 fG0 4,
|
2016-02-10 10:50:38 +03:00
|
|
|
portToPort fRecurAp 1 fTimesAp 3,
|
2016-01-23 05:08:53 +03:00
|
|
|
--iconToPort fArg fTimesAp 2,
|
|
|
|
iconToPort fRes fG0 0
|
|
|
|
]
|
|
|
|
|
|
|
|
fact2Drawing = Drawing fact2Icons fact2Edges []
|
|
|
|
|
|
|
|
factLam2Edges = [
|
|
|
|
iconToPort ("lam0" .> fTimesAp .> (2 :: Int)) "lam0" 0,
|
|
|
|
iconToPort "lam0" ("lam0" .> fRecurAp) 0,
|
|
|
|
iconToIcon "lam0" "fac"
|
|
|
|
]
|
|
|
|
factLam2Drawing = Drawing factLam0Icons factLam2Edges [(fact0Name, fact2Drawing)]
|
|
|
|
|
2016-01-23 04:06:42 +03:00
|
|
|
(arr1, arr2, arr3, arr4) = ("arr1", "arr2", "arr3", "arr4")
|
|
|
|
|
|
|
|
arrowTestIcons = toNames [
|
|
|
|
(arr1, TextBoxIcon "1"),
|
|
|
|
(arr2, TextBoxIcon "2"),
|
|
|
|
(arr3, TextBoxIcon "3"),
|
|
|
|
(arr4, TextBoxIcon "4")
|
|
|
|
]
|
|
|
|
|
|
|
|
arrowTestEdges = [
|
|
|
|
iconToIconEnds arr1 EndAp1Arg arr2 EndAp1Result,
|
|
|
|
iconToIconEnds arr1 EndAp1Result arr3 EndAp1Arg,
|
|
|
|
iconToIconEnds arr2 EndAp1Result arr3 EndAp1Result,
|
|
|
|
iconToIconEnds arr1 EndAp1Arg arr4 EndAp1Arg
|
|
|
|
]
|
|
|
|
|
|
|
|
arrowTestDrawing = Drawing arrowTestIcons arrowTestEdges []
|
|
|
|
|
2016-01-09 08:52:41 +03:00
|
|
|
main1 :: IO ()
|
2016-01-09 04:53:12 +03:00
|
|
|
main1 = do
|
2016-02-10 10:50:38 +03:00
|
|
|
placedNodes <- renderDrawing factLam0Drawing
|
2016-01-23 06:42:15 +03:00
|
|
|
mainWith ((placedNodes # bgFrame 1 (backgroundC colorScheme)) :: Diagram B)
|
2016-01-08 04:03:04 +03:00
|
|
|
|
2016-01-23 06:42:15 +03:00
|
|
|
main2 = mainWith ((apply0NDia 3 # bgFrame 0.1 black) :: Diagram B)
|
2016-01-14 00:50:06 +03:00
|
|
|
|
2016-02-10 10:50:38 +03:00
|
|
|
main3 :: IO ()
|
|
|
|
main3 = do
|
|
|
|
renderedDiagrams <- mapM renderDrawing allDrawings
|
|
|
|
let vCattedDrawings = vcat' (with & sep .~ 0.5) renderedDiagrams
|
|
|
|
mainWith ((vCattedDrawings # bgFrame 1 (backgroundC colorScheme)) :: Diagram B)
|
|
|
|
where
|
|
|
|
allDrawings = [
|
|
|
|
drawing0,
|
|
|
|
superDrawing,
|
|
|
|
super2Drawing,
|
|
|
|
super3Drawing,
|
|
|
|
fact0Drawing,
|
|
|
|
factLam0Drawing,
|
|
|
|
fact1Drawing,
|
|
|
|
factLam1Drawing,
|
|
|
|
fact2Drawing,
|
|
|
|
factLam2Drawing,
|
|
|
|
arrowTestDrawing
|
|
|
|
]
|
|
|
|
|
2016-02-06 09:39:05 +03:00
|
|
|
testDecls = [
|
2016-02-18 10:14:14 +03:00
|
|
|
"y x1 x2 x3 = if f x1 then g x2 else h x3",
|
|
|
|
"y x1 x2 x3 = if x1 then x2 else x3",
|
|
|
|
"y = if b then x else n",
|
2016-02-18 04:31:11 +03:00
|
|
|
"y = (\\x -> (\\x -> (\\x -> x) x) x)",
|
|
|
|
"y = (\\x -> (\\x -> (\\x -> x)))",
|
|
|
|
"y = (\\y -> y)",
|
|
|
|
"y = (\\x1 -> (\\x2 -> (\\x3 -> x1 x2 x3)))",
|
2016-02-18 02:36:57 +03:00
|
|
|
"y x = (\\z -> x)",
|
|
|
|
"y = (\\x -> (\\z -> x))",
|
2016-02-18 04:31:11 +03:00
|
|
|
"y x = x"
|
|
|
|
-- "y x = y x",
|
|
|
|
-- "y x = g y y",
|
|
|
|
-- "y f x = f x",
|
|
|
|
-- "y x = x y"
|
2016-02-18 02:36:57 +03:00
|
|
|
-- "y x1 x2 = f x1 x3 x2",
|
|
|
|
-- "y x1 x2 = f x1 x2",
|
|
|
|
-- "y x = f x1 x2",
|
|
|
|
-- "y2 = f x1 x2 x3 x4",
|
|
|
|
-- "y = x",
|
|
|
|
-- "y = f x",
|
|
|
|
-- "y = f (g x)",
|
|
|
|
-- "y = f (g x1 x2) x3",
|
|
|
|
-- "y = (f x1 x2) (g x1 x2)"
|
2016-02-06 09:39:05 +03:00
|
|
|
]
|
|
|
|
|
|
|
|
translateStringToDrawing :: String -> IO (Diagram B)
|
|
|
|
translateStringToDrawing s = do
|
2016-02-04 11:19:08 +03:00
|
|
|
let
|
2016-02-06 09:39:05 +03:00
|
|
|
(drawing, decl) = translateString s
|
2016-02-04 11:19:08 +03:00
|
|
|
print decl
|
2016-02-09 08:54:23 +03:00
|
|
|
putStr "\n"
|
2016-02-05 08:53:21 +03:00
|
|
|
print drawing
|
2016-02-09 08:54:23 +03:00
|
|
|
putStr "\n\n"
|
2016-02-06 09:39:05 +03:00
|
|
|
renderDrawing drawing
|
|
|
|
|
2016-02-10 10:50:38 +03:00
|
|
|
main4 :: IO ()
|
|
|
|
main4 = do
|
2016-02-06 09:39:05 +03:00
|
|
|
drawings <- mapM translateStringToDrawing testDecls
|
2016-02-08 05:01:57 +03:00
|
|
|
let vCattedDrawings = vcat' (with & sep .~ 0.5) drawings
|
2016-02-06 09:39:05 +03:00
|
|
|
mainWith ((vCattedDrawings # bgFrame 1 (backgroundC colorScheme)) :: Diagram B)
|
2016-02-04 11:19:08 +03:00
|
|
|
|
2016-01-05 04:18:42 +03:00
|
|
|
main :: IO ()
|
2016-02-10 10:50:38 +03:00
|
|
|
main = main4
|