("app"))
32 | with :? FsiEvaluationException as e ->
33 | traceError "Reloading app.fsx script failed."
34 | traceError (sprintf "Message: %s\nError: %s" e.Message e.Result.Error.Merged)
35 | None
36 |
37 | // --------------------------------------------------------------------------------------
38 | // Suave server that redirects all request to currently loaded WebPart. We watch for
39 | // changes & reload automatically. The WebPart is then hosted at http://localhost:8087
40 | // --------------------------------------------------------------------------------------
41 |
42 | let currentApp = ref (fun _ -> async { return None })
43 |
44 | let serverConfig =
45 | { defaultConfig with
46 | homeFolder = Some __SOURCE_DIRECTORY__
47 | logger = Logging.Loggers.saneDefaultsFor Logging.LogLevel.Debug
48 | bindings = [ HttpBinding.mk' HTTP "127.0.0.1" 8087] }
49 |
50 | let reloadAppServer () =
51 | reloadScript() |> Option.iter (fun app ->
52 | currentApp.Value <- app
53 | traceImportant "New version of app.fsx loaded!" )
54 |
55 | Target "Run" (fun _ ->
56 | let app ctx = currentApp.Value ctx
57 | let _, server = startWebServerAsync serverConfig app
58 |
59 | // Start Suave & open web browser with the site
60 | reloadAppServer()
61 | Async.Start(server)
62 | //System.Diagnostics.Process.Start("http://localhost:8087") |> ignore
63 |
64 | // Watch for changes & reload when app.fsx changes
65 | let sources = { BaseDirectory = __SOURCE_DIRECTORY__; Includes = [ "**/*.fs*" ]; Excludes = [] }
66 | use watcher = sources |> WatchChanges (fun _ -> reloadAppServer())
67 | traceImportant "Waiting for app.fsx edits. Press any key to stop."
68 |
69 | async {
70 | while not(System.IO.File.Exists(__SOURCE_DIRECTORY__ @@ ".stop")) do
71 | do! Async.Sleep(500)
72 | System.Diagnostics.Process.GetCurrentProcess().Kill() }
73 | |> Async.Start
74 |
75 | System.Console.ReadLine() |> ignore
76 | )
77 |
78 | Target "Build" ignore
79 |
80 | // --------------------------------------------------------------------------------------
81 | // Minimal Azure deploy script - just overwrite old files with new ones
82 | // --------------------------------------------------------------------------------------
83 |
84 | Target "Deploy" (fun _ ->
85 | let sourceDirectory = __SOURCE_DIRECTORY__
86 | let wwwrootDirectory = __SOURCE_DIRECTORY__ @@ "../../wwwroot"
87 | CleanDir wwwrootDirectory
88 | CopyRecursive sourceDirectory wwwrootDirectory false |> ignore
89 | (*
90 | try
91 | DeleteDir wwwrootDirectory
92 | CreateDir wwwrootDirectory
93 | with e ->
94 | printfn "Could not delete all files in %s" wwwrootDirectory
95 | try
96 | CopyRecursive sourceDirectory wwwrootDirectory false |> ignore
97 | with e ->
98 | printfn "Copying files failed with: %A" e
99 | reraise()
100 | *)
101 | )
102 |
103 | RunTargetOrDefault "Run"
104 |
--------------------------------------------------------------------------------
/slides/future-programming-video/slides/index.md:
--------------------------------------------------------------------------------
1 | - title : The Gamma
2 | - description : Data journalism
3 | - author : Tomas Petricek
4 | - theme : night
5 | - transition : none
6 |
7 | ***************************************************************************************************
8 | - class: intro
9 |
10 |
60 |
61 | # The Gamma
62 |
63 | [www.thegamma.net](http://thegamma.net)
64 |
65 |
66 |
67 | **Tomas Petricek**
68 | [_@tomaspetricek_](http://twitter.com/tomaspetricek) |
69 | [_tomas@tomasp.net_](mailto:tomas@tomasp.net)
70 |
71 | ***************************************************************************************************
72 |
73 | ## Data journalism tools
74 |
75 |
76 |
77 | Future of working with information
78 |
79 |
80 |
81 | - Telling _stories with data_
82 | - Let the reader do **further investigations**
83 | - Journalists _become programmers_
84 |
85 |
86 |
87 | ***************************************************************************************************
88 |
89 | # DEMO
90 |
91 | ## Data driven articles
92 |
93 | ***************************************************************************************************
94 |
95 | ## More than just an article
96 |
97 |
98 |
99 | Can the reader see what's behind it?
100 |
101 |
102 |
103 | - Can it be _modified and reproduced_?
104 | - Is the **source code** available?
105 | - Are the _data sources_ credible?
106 |
107 |
108 |
109 | ***************************************************************************************************
110 |
111 | # DEMO
112 |
113 | ## Article is a program
114 |
115 | ***************************************************************************************************
116 |
117 | ## Article is a program view
118 |
119 |
120 |
121 | There is no magic. It is just code and text!
122 |
123 |
124 |
125 | - We first see the _final story_
126 | - We can **modify** the parameters
127 | - We can _understand_ how it works
128 |
129 |
130 |
131 | ***************************************************************************************************
132 |
133 | # DEMO
134 |
135 | ## The technology
136 |
137 | ***************************************************************************************************
138 |
139 | ## The technology
140 |
141 |
142 |
143 | Programming language research
144 |
145 |
146 |
147 | - Simple _functional programming_
148 | - Using **static types** for the editor
149 | - F# _type providers_ for data access
150 |
151 |
152 |
153 | ***************************************************************************************************
154 |
155 | ## Summary
156 |
157 |
158 |
159 | Is programming the new literacy?
160 |
161 |
162 |
163 | - _Understanding_ information is
164 | - **Programming** needs to adapt
165 | - Check out the _prototype_!
166 |
167 |
168 |
169 |
170 |
171 | [thegamma.net](http://thegamma.net) |
172 | [_@tomaspetricek_](http://twitter.com/tomaspetricek) |
173 | [_tomas@tomasp.net_](mailto:tomas@tomasp.net)
174 |
175 |
176 |
--------------------------------------------------------------------------------
/slides/future-programming-video/build.fsx:
--------------------------------------------------------------------------------
1 | #I @"packages/FsReveal/fsreveal/"
2 | #I @"packages/FAKE/tools/"
3 | #I @"packages/Suave/lib/net40"
4 |
5 | #r "FakeLib.dll"
6 | #r "suave.dll"
7 |
8 | #load "fsreveal.fsx"
9 |
10 | // Git configuration (used for publishing documentation in gh-pages branch)
11 | // The profile where the project is posted
12 | let gitOwner = "myGitUser"
13 | let gitHome = "https://github.com/" + gitOwner
14 | // The name of the project on GitHub
15 | let gitProjectName = "MyProject"
16 |
17 | open FsReveal
18 | open Fake
19 | open Fake.Git
20 | open System.IO
21 | open System.Diagnostics
22 | open Suave
23 | open Suave.Web
24 | open Suave.Http
25 | open Suave.Http.Files
26 |
27 | let outDir = __SOURCE_DIRECTORY__ @@ "output"
28 | let slidesDir = __SOURCE_DIRECTORY__ @@ "slides"
29 |
30 | Target "Clean" (fun _ ->
31 | CleanDirs [outDir]
32 | )
33 |
34 | let fsiEvaluator =
35 | let evaluator = FSharp.Literate.FsiEvaluator()
36 | evaluator.EvaluationFailed.Add(fun err ->
37 | traceImportant <| sprintf "Evaluating F# snippet failed:\n%s\nThe snippet evaluated:\n%s" err.StdErr err.Text )
38 | evaluator
39 |
40 | let copyStylesheet() =
41 | try
42 | CopyFile (outDir @@ "css" @@ "custom.css") (slidesDir @@ "custom.css")
43 | with
44 | | exn -> traceImportant <| sprintf "Could not copy stylesheet: %s" exn.Message
45 |
46 | let copyPics() =
47 | try
48 | CopyDir (outDir @@ "images") (slidesDir @@ "images") (fun f -> true)
49 | with
50 | | exn -> traceImportant <| sprintf "Could not copy picture: %s" exn.Message
51 |
52 | let generateFor (file:FileInfo) =
53 | try
54 | copyPics()
55 | let rec tryGenerate trials =
56 | try
57 | FsReveal.GenerateFromFile(file.FullName, outDir, fsiEvaluator = fsiEvaluator)
58 | with
59 | | exn when trials > 0 -> tryGenerate (trials - 1)
60 | | exn ->
61 | traceImportant <| sprintf "Could not generate slides for: %s" file.FullName
62 | traceImportant exn.Message
63 |
64 | tryGenerate 3
65 |
66 | copyStylesheet()
67 | with
68 | | :? FileNotFoundException as exn ->
69 | traceImportant <| sprintf "Could not copy file: %s" exn.FileName
70 |
71 | let handleWatcherEvents (e:FileSystemEventArgs) =
72 | let fi = fileInfo e.FullPath
73 | traceImportant <| sprintf "%s was changed." fi.Name
74 | match fi.Attributes.HasFlag FileAttributes.Hidden || fi.Attributes.HasFlag FileAttributes.Directory with
75 | | true -> ()
76 | | _ -> generateFor fi
77 |
78 | let startWebServer () =
79 | let serverConfig =
80 | { defaultConfig with
81 | homeFolder = Some (FullName outDir)
82 | }
83 | let app =
84 | Writers.setHeader "Cache-Control" "no-cache, no-store, must-revalidate"
85 | >>= Writers.setHeader "Pragma" "no-cache"
86 | >>= Writers.setHeader "Expires" "0"
87 | >>= browseHome
88 | startWebServerAsync serverConfig app |> snd |> Async.Start
89 | Process.Start "http://localhost:8083/index.html" |> ignore
90 |
91 | Target "GenerateSlides" (fun _ ->
92 | // Overwrite the default template with my custom one!
93 | (slidesDir @@ "template.html")
94 | |> CopyFile (slidesDir @@ "../packages/FsReveal/fsreveal/template.html")
95 |
96 | !! (slidesDir @@ "*.md")
97 | ++ (slidesDir @@ "*.fsx")
98 | |> Seq.map fileInfo
99 | |> Seq.iter generateFor
100 | )
101 |
102 | Target "KeepRunning" (fun _ ->
103 | use watcher = new FileSystemWatcher(FullName slidesDir,"*.*")
104 | watcher.EnableRaisingEvents <- true
105 | watcher.IncludeSubdirectories <- true
106 | watcher.Changed.Add(handleWatcherEvents)
107 | watcher.Created.Add(handleWatcherEvents)
108 | watcher.Renamed.Add(handleWatcherEvents)
109 |
110 | startWebServer ()
111 |
112 | traceImportant "Waiting for slide edits. Press any key to stop."
113 |
114 | System.Console.ReadKey() |> ignore
115 |
116 | watcher.EnableRaisingEvents <- false
117 | watcher.Dispose()
118 | )
119 |
120 | Target "ReleaseSlides" (fun _ ->
121 | if gitOwner = "myGitUser" || gitProjectName = "MyProject" then
122 | failwith "You need to specify the gitOwner and gitProjectName in build.fsx"
123 | let tempDocsDir = __SOURCE_DIRECTORY__ @@ "temp/gh-pages"
124 | CleanDir tempDocsDir
125 | Repository.cloneSingleBranch "" (gitHome + "/" + gitProjectName + ".git") "gh-pages" tempDocsDir
126 |
127 | fullclean tempDocsDir
128 | CopyRecursive outDir tempDocsDir true |> tracefn "%A"
129 | StageAll tempDocsDir
130 | Git.Commit.Commit tempDocsDir "Update generated slides"
131 | Branches.push tempDocsDir
132 | )
133 |
134 | "Clean"
135 | ==> "GenerateSlides"
136 | ==> "KeepRunning"
137 |
138 | "GenerateSlides"
139 | ==> "ReleaseSlides"
140 |
141 | RunTargetOrDefault "KeepRunning"
142 |
--------------------------------------------------------------------------------
/web/code/evaluator.fs:
--------------------------------------------------------------------------------
1 | module TheGamma.Server.Evaluator
2 |
3 | open Microsoft.FSharp.Compiler.Ast
4 | open Microsoft.FSharp.Compiler.Interactive.Shell
5 | open Microsoft.FSharp.Compiler.SourceCodeServices
6 | open System
7 | open System.IO
8 | open System.Text
9 | open TheGamma.Server.Common
10 |
11 | // ------------------------------------------------------------------------------------------------
12 | // FunScript + F# Compiler Service Evaluator
13 | // ------------------------------------------------------------------------------------------------
14 |
15 | type FsiSession =
16 | { Session : FsiEvaluationSession
17 | ErrorString : StringBuilder }
18 |
19 | /// Start F# Interactive, reference all assemblies in `refFolder`
20 | /// evaluate the initial `loadScript` and return running 'FsiSession'
21 | let startSession refFolder loadScript =
22 | let sbOut = new StringBuilder()
23 | let sbErr = new StringBuilder()
24 | let inStream = new StringReader("")
25 | let outStream = new StringWriter(sbOut)
26 | let errStream = new StringWriter(sbErr)
27 |
28 | // Start the F# Interactive service process
29 | let refFiles = Directory.GetFiles(refFolder, "*.dll")
30 | let fsiConfig = FsiEvaluationSession.GetDefaultConfiguration()
31 | let fsiSession =
32 | FsiEvaluationSession.Create
33 | ( fsiConfig, [| "/temp/fsi.exe"; "--noninteractive" |],
34 | inStream, outStream, errStream, collectible = true )
35 |
36 | // Load referenced libraries & run initialization script
37 | try
38 | fsiSession.EvalInteraction(sprintf "#I @\"%s\"" refFolder)
39 | for lib in refFiles do fsiSession.EvalInteraction(sprintf "#r @\"%s\"" lib)
40 | fsiSession.EvalInteraction(loadScript)
41 | { Session = fsiSession; ErrorString = sbErr }
42 | with _ -> failwithf "F# Interactive initialization failed: %s" (sbErr.ToString())
43 |
44 |
45 | /// Check that the user didn't do anything to escape quoted expression
46 | /// (i.e. they are not trying to run any code on our server..)
47 | let checkScriptStructure (scriptFile, source) (checker:FSharpChecker) = async {
48 | let! options = checker.GetProjectOptionsFromScript(scriptFile, source)
49 | let! parsed = checker.ParseFileInProject(scriptFile, source, options)
50 | match parsed.ParseTree with
51 | | Some tree ->
52 | match tree with
53 | // Expecting: single file containing single module named "Script"
54 | | ParsedInput.ImplFile
55 | (ParsedImplFileInput(_,_,_,_,_,[SynModuleOrNamespace([id],_,decls,_,_,_,_)],_))
56 | when id.idText = "Script" ->
57 | match decls with
58 | // Expecting: FunScript.Compiler.Compiler.Compile(<@ .. @>)
59 | // (if all user code is inside quotation, it does not get run)
60 | | [ SynModuleDecl.DoExpr
61 | (_, SynExpr.App
62 | ( _, _, SynExpr.LongIdent _,
63 | SynExpr.Paren(SynExpr.Quote _, _, _, _), _), _) ] -> ()
64 | | _ -> failwith "Unexpected AST!"
65 | | _ -> failwith "Unexpected AST!"
66 | | _ -> failwith "Could not parse the specified AST" }
67 |
68 | /// Pass the specified code to FunScript and return JavaScript that we'll
69 | /// send back to the client (so that they can run it themselves)
70 | let evalFunScript code { Session = fsiSession; ErrorString = sbErr } = async {
71 | let allCode =
72 | [ yield "FunScript.Compiler.Compiler.Compile(<@"
73 | for line in getLines code do yield " " + line
74 | yield "@>)" ]
75 | |> String.concat "\n"
76 | printfn "Evaluating: %s" allCode
77 | do! checkScriptStructure (Config.scriptFile, allCode) fsiSession.InteractiveChecker
78 |
79 | try
80 | match fsiSession.EvalExpression(allCode) with
81 | | Some value -> return Choice1Of2(value.ReflectionValue.ToString())
82 | | None -> return Choice2Of2(new Exception("Evaluating expression produced no output."))
83 | with e ->
84 | let errors = sbErr.ToString()
85 | return Choice2Of2(new Exception("Evaluation failed: " + errors, e)) }
86 |
87 | // ------------------------------------------------------------------------------------------------
88 | // Start F# interactive and expose a web part
89 | // ------------------------------------------------------------------------------------------------
90 |
91 | open Suave.Http
92 | open Suave.Http.Applicatives
93 |
94 | let cache = System.Collections.Concurrent.ConcurrentDictionary()
95 |
96 | let evaluate (fsi:ResourceAgent) code = async {
97 | match cache.TryGetValue(code) with
98 | | true, (_, res) ->
99 | printfn "----- reading from cache"
100 | return res
101 | | _ ->
102 | printfn "----- calculating"
103 | let! res = fsi.Process(evalFunScript code)
104 | cache.[code] <- (DateTime.UtcNow, res)
105 | return res }
106 |
107 | let webPart fsi =
108 | path "/run" >>= withRequestParams (fun (_, _, source) ctx -> async {
109 | // Transform F# `source` into JavaScript and return it
110 | let! jscode = evaluate fsi source
111 | match jscode with
112 | | Choice1Of2 jscode -> return! ctx |> noCacheSuccess jscode
113 | | Choice2Of2 e ->
114 | printfn "Evalutaiton failed: %s" (e.ToString())
115 | return! ctx |> RequestErrors.BAD_REQUEST "evaluation failed" })
116 |
--------------------------------------------------------------------------------
/web/demos/carbon.md:
--------------------------------------------------------------------------------
1 | The world's biggest polluters
2 | =============================
3 |
4 | Which countries of the world are responsible for the global
5 | warming? Looking at the data over the last 50 years tells us
6 | quite a lot - not just about the biggest polluters, but also
7 | about how the world has changed!
8 |
9 | Carbon emissions today
10 | ----------------------
11 |
12 | If we look at CO2 emissions for the whole world for recent years,
13 | we can see the expected results. In general, the rich countries
14 | in America and Europe together with China and India are producing
15 | large percentage of the world's CO2 emissions. The map also shows
16 | the next group: Iran, Australia, Canada, Brazil and Saudi Arabia:
17 |
18 | let colorScale =
19 | [ "#6CC627";"#DB9B3B";"#DB7532";
20 | "#DD5321";"#DB321C";"#E00B00"]
21 |
22 | let co2 =
23 | world.byYear.``2010``.``Climate Change``
24 | .``CO2 emissions (kt)``
25 |
26 | chart.geo(co2)
27 | .colorAxis(colors=colorScale).show()
28 |
29 | The largest producer of carbon dioxide (CO2) in the world is China.
30 | In the year 2010, it produced over 8 millions of kilotons of CO2.
31 | The list of the biggest polluters continues with the United States
32 | (producing 5.4 millions), India (1.9 millions) and Russia. You can
33 | see more in the table below.
34 |
35 | A curious fact is that the smallest producer of CO2 emissions is
36 | Liechtenstein with just 58 kilotons per year, followed by small
37 | island countries of the Pacific and Africa.
38 |
39 | let countries =
40 | world.byYear.``2010``.``Climate Change``
41 | .``CO2 emissions (kt)``
42 | .sortValues(reverse=true)
43 | .take(10)
44 |
45 | table.create(countries).show()
46 |
47 | If we look at the share of CO2 emissions for individual countries, we
48 | can see that China produces over one quarter (26.4%) of all the CO2 of the
49 | world. In fact, the first three countries (China, US and India) are
50 | responsible for almost an exact half (49.9%) of the world's CO2:
51 |
52 | let countries =
53 | world.byYear.``2010``.``Climate Change``
54 | .``CO2 emissions (kt)``.sortValues(reverse=true)
55 |
56 | let sumRest =
57 | countries.skip(6).sum()
58 | let topAndRest =
59 | countries.take(6)
60 | .append("Other countries", sumRest)
61 | chart.pie(topAndRest).show()
62 |
63 | Looking at the data for the year 2010 shows the expected results
64 | with China, USA and India on the top of the list. But this is also
65 | because these three are very large countries.
66 |
67 | Emissions per capita
68 | --------------------
69 |
70 | To see a somewhat different picture, let's look at carbon emissions
71 | per capita. That is, the CO2 emissions for a single person living
72 | in each of the countries. As you can see in the following map, a
73 | very different picture appears:
74 |
75 | let climate =
76 | world.byYear
77 | .``2010``.``Climate Change``
78 | let co2 =
79 | climate.``CO2 emissions (kt)``
80 | let population =
81 | climate.``Population, total``
82 |
83 | let pcp =
84 | co2.joinInner(population)
85 | .map(fun (co2, pop) -> co2 / pop)
86 |
87 | let colorScale =
88 | [ "#6CC627";"#DB9B3B";"#DB7532";
89 | "#DD5321";"#DB321C";"#E00B00"]
90 |
91 | chart.geo(pcp)
92 | .colorAxis(colors=colorScale).show()
93 |
94 | Quite different set of countries appear when compared to the
95 | previous visualization. The biggest polluters per capita include
96 | small Persian Gulf states including Quatar, Kuwait, UAR and Oman,
97 | followed by large developed countries (USA, Canada and Australia).
98 | We can still see China among the polluters too, but India almost
99 | completely disappears.
100 |
101 | Carbon emissions in the past
102 | ----------------------------
103 |
104 | Although the biggest polluters of the modern world, and especially
105 | China, are contributing a large part of the overall emissions
106 | today, this only started happening in recent years. If we look at
107 | the past, we see yet another picture. For example, in the year
108 | 1960, the biggest polluter by far was the United States.
109 |
110 | The following map shows the data for the year 1960. The World Bank
111 | does not have the data for the former Easter block countries,
112 | and so the values there are missing.
113 |
114 | let colorScale =
115 | [ "#6CC627";"#DB9B3B";"#DB7532";
116 | "#DD5321";"#DB321C";"#E00B00"]
117 |
118 | let co2 =
119 | world.byYear.``1960``.``Climate Change``
120 | .``CO2 emissions (kt)``
121 |
122 | chart.geo(co2)
123 | .colorAxis(colors=colorScale).show()
124 |
125 | So, when did China become the biggest polluter in the world?
126 | Quite surprisingly, this is only a recent development. As you
127 | can see in our final visualization, the CO2 emissions of China
128 | began growing rapidly around the year 2002, it overtook the
129 | USA around 2005 and it continues growing.
130 |
131 | let topCountries =
132 | [ world.byCountry.China
133 | world.byCountry.India
134 | world.byCountry.Japan
135 | world.byCountry.``Russian Federation``
136 | world.byCountry.``United States`` ]
137 |
138 | let growths =
139 | topCountries.map(fun p ->
140 | p.``Climate Change``.``CO2 emissions (kt)``
141 | .set(seriesName=p.name) )
142 |
143 | chart.line(growths).show()
144 |
--------------------------------------------------------------------------------
/web/code/document.fs:
--------------------------------------------------------------------------------
1 | module TheGamma.Server.Document
2 |
3 | // ------------------------------------------------------------------------------------------------
4 | // Suave.io web server
5 | // ------------------------------------------------------------------------------------------------
6 |
7 | open System
8 | open System.IO
9 | open Suave
10 | open Suave.Web
11 | open Suave.Http
12 | open Suave.Types
13 | open FSharp.Markdown
14 |
15 | let invalidChars = set(Path.GetInvalidFileNameChars())
16 | let pageTemplatePath = Path.Combine(__SOURCE_DIRECTORY__, "..", "templates", "page-template.html")
17 | let iframeTemplatePath = Path.Combine(__SOURCE_DIRECTORY__, "..", "templates", "iframe-template.html")
18 | let editorTemplatePath = Path.Combine(__SOURCE_DIRECTORY__, "..", "templates", "editor-template.html")
19 | let docpartTemplatePath = Path.Combine(__SOURCE_DIRECTORY__, "..", "templates", "docpart-template.html")
20 |
21 | type DocumentChunk =
22 | | Code of string
23 | | Text of MarkdownParagraphs
24 |
25 | let rec chunkByCodeBlocks acc pars = seq {
26 | match pars with
27 | | [] ->
28 | if acc <> [] then yield Text(List.rev acc)
29 | | CodeBlock(code, _, _) :: pars ->
30 | if acc <> [] then yield Text(List.rev acc)
31 | yield Code(code)
32 | yield! chunkByCodeBlocks [] pars
33 | | par :: pars ->
34 | yield! chunkByCodeBlocks (par::acc) pars }
35 |
36 | let formatMarkdownSpan span (sb:Text.StringBuilder) =
37 | match span with
38 | | MarkdownSpan.Literal(s) -> sb.Append(s)
39 | | MarkdownSpan.InlineCode(s) -> sb.Append("`" + s + "`")
40 | | span -> sb.Append(sprintf "ERROR: %A" span)
41 |
42 | let formatMarkdownSpans spans sb =
43 | spans |> Seq.iter (fun s -> formatMarkdownSpan s sb |> ignore); sb
44 |
45 | let formatMarkdownPar par (sb:Text.StringBuilder) =
46 | match par with
47 | | MarkdownParagraph.Paragraph(spans) ->
48 | (formatMarkdownSpans spans sb).Append("\n\n")
49 | | MarkdownParagraph.Heading(n, body) ->
50 | if n = 1 || n = 2 then
51 | let lengthBefore = sb.Length
52 | (formatMarkdownSpans body sb).Append("\n")
53 | .Append(String.replicate (sb.Length - lengthBefore) (if n = 1 then "=" else "-")) |> ignore
54 | else
55 | sb.Append(String.replicate n "#").Append(" ")
56 | |> formatMarkdownSpans body |> ignore
57 | sb.Append("\n\n")
58 | | span -> sb.Append(sprintf "ERROR: %A" span)
59 |
60 | let formatMarkdownPars pars sb =
61 | pars |> Seq.iter (fun s -> formatMarkdownPar s sb |> ignore); sb
62 |
63 | let transformBlock (doc:MarkdownDocument) fsi counter block = async {
64 | incr counter
65 | let id = "output_" + (string counter.Value)
66 |
67 | match block with
68 | | Text pars ->
69 | let html = Markdown.WriteHtml(MarkdownDocument(pars, doc.DefinedLinks))
70 | let docpartTemplate = File.ReadAllText(docpartTemplatePath)
71 | let source = (formatMarkdownPars pars (Text.StringBuilder())).ToString()
72 | let encoded = System.Web.HttpUtility.JavaScriptStringEncode(source)
73 | return docpartTemplate.Replace("[ID]", id).Replace("[BODY]", html).Replace("[SOURCE]", encoded)
74 |
75 | | Code code ->
76 | let! js = Evaluator.evaluate fsi code
77 | match js with
78 | | Choice1Of2(js) ->
79 | let editorTemplate = File.ReadAllText(editorTemplatePath)
80 | let encoded = System.Web.HttpUtility.JavaScriptStringEncode(code)
81 | return editorTemplate.Replace("[ID]", id).Replace("[SCRIPT]", js).Replace("[SOURCE]", encoded)
82 | | Choice2Of2(err) -> return err.ToString() }
83 |
84 | let transform fsi template path = async {
85 | let pageTemplate = File.ReadAllText(template)
86 | let doc = Markdown.Parse(File.ReadAllText(path))
87 | let blocks = doc.Paragraphs |> chunkByCodeBlocks [] |> List.ofSeq
88 |
89 | let! newPars = Common.asyncMap (transformBlock doc fsi (ref 0)) blocks
90 | return pageTemplate.Replace("[BODY]", String.concat "\n" newPars) }
91 |
92 | let renderMarkdown md =
93 | Markdown.TransformHtml(md)
94 |
95 | let renderDocument fsi ctx = async {
96 | let file = ctx.request.url.LocalPath
97 | if file.[0] <> '/' || (Seq.exists invalidChars.Contains file.[1 ..]) then return None else
98 | let path = Path.Combine(__SOURCE_DIRECTORY__, "..", "demos", file.Substring(1) + ".md")
99 | if File.Exists(path) then
100 | printfn "Processing file: %s" path
101 | match ctx.request.queryParam "export" with
102 | | Choice1Of2 s ->
103 | // Export the specified javascript functions
104 | let doc = Markdown.Parse(File.ReadAllText(path))
105 | let code = doc.Paragraphs |> List.pick (function CodeBlock(code, _, _) -> Some code | _ -> None)
106 | let code = code + "[|" + String.concat ";" [ for f in s.Split(',') -> "box " + f ] + "|]"
107 | let! js = Evaluator.evaluate fsi code
108 | let js = match js with Choice1Of2 js -> js | _ -> ""
109 | let js = "var exports = (function() { " + js + "})();\n"
110 | let exports =
111 | s.Split(',') |> Seq.mapi (fun i f ->
112 | sprintf "var %s = exports[%d];" f i)
113 | |> String.concat "\n"
114 | return! ctx |> Successful.OK(js + exports)
115 |
116 | | _ ->
117 | // Process document using normal or iframe template
118 | let template =
119 | match ctx.request.queryParam "iframe" with
120 | | Choice1Of2 _ -> iframeTemplatePath
121 | | _ -> pageTemplatePath
122 | let! html = transform fsi template path
123 | return! ctx |> Successful.OK(html)
124 | else return None }
125 |
126 | open Suave.Http.Applicatives
127 |
128 | let webPart fsi =
129 | choose
130 | [ renderDocument fsi
131 | path "/markdown" >>= Common.withRequestParams (fun (_, _, body) ->
132 | printfn "Transform markdown: %s" body
133 | Successful.OK(renderMarkdown body)) ]
134 |
--------------------------------------------------------------------------------
/web/web/content/site.css:
--------------------------------------------------------------------------------
1 | @import url(http://fonts.googleapis.com/css?family=Rufina:300,400,700|Pontano+Sans:400,700,400italic);
2 |
3 | /****************************** Fancy header with a fancy effect *******************************/
4 | header{
5 | position: fixed;
6 | width: 100%;
7 | height: 110px;
8 | background: black;
9 | color: white;
10 | transition:all 1s;
11 | z-index:100;
12 | border-bottom:10px solid white;
13 | }
14 | header.scrolled {
15 | height:70px;
16 | padding-top: 0px;
17 | }
18 | header h1 {
19 | font:bold 40pt Rufina,'Times New Roman', Times, serif;
20 | color:white;
21 | padding:0px;
22 | margin:15px 0px 0px 0px;
23 | transition:all 1s;
24 | }
25 | header.scrolled h1 {
26 | font:bold 20pt Rufina,'Times New Roman', Times, serif;
27 | color:white;
28 | }
29 | #main {
30 | position:relative;
31 | top:140px;
32 | transition:top 1s;
33 | }
34 | header .icons a, header .icons a:visited, header .icons a:hover {
35 | float:right;
36 | border-radius:20px;
37 | background:white;
38 | padding:2px 0px 0px 6px;
39 | display:block;
40 | width:40px;
41 | height:40px;
42 | font-size:25px;
43 | color:black;
44 | margin:15px 20px 0px 2px;
45 |
46 | transition:all 1s;
47 | }
48 |
49 | header .icons a i {
50 | margin-left: 1px;
51 | }
52 |
53 | header.scrolled .icons a {
54 | border-radius:15px;
55 | padding:0px 0px 0px 6px;
56 | width:30px;
57 | height:30px;
58 | font-size:20px;
59 | margin-top:2px;
60 | margin-left: 0;
61 | }
62 |
63 | header.scrolled .icons a i {
64 | margin-left: -1px;
65 | }
66 |
67 | @media (min-width:768px)
68 | {
69 | header .icons a, header .icons a:visited, header .icons a:hover {
70 | margin-top:25px;
71 | }
72 | header.scrolled .icons a {
73 | margin-top:10px;
74 | }
75 | }
76 | /****************************** Editor wrapper and output *******************************/
77 |
78 | /* Wrapper around the Markdown editor */
79 | .doc-wrapper {
80 | background:white;
81 | border:1px solid #e0e0e0;
82 | border-radius:2px;
83 | margin:20px;
84 | padding:10px 10px 5px 10px;
85 | }
86 | .cm-header {
87 | color:#d0d0d0 !important;
88 | }
89 |
90 | /* The whole box */
91 | .editor-wrapper {
92 | background:#f8f8f8;
93 | border:1px solid #e0e0e0;
94 | border-radius:2px;
95 | margin:20px;
96 | padding:10px;
97 | }
98 |
99 | .editor-output {
100 | margin:10px;
101 | }
102 |
103 | /* White background once loaded & loading tools */
104 | .loaded {
105 | background:white;
106 | }
107 |
108 | .loading {
109 | padding:50px;
110 | text-align:center;
111 | }
112 |
113 | .loading p {
114 | margin-bottom:30px;
115 | color:#d0d0d0;
116 | }
117 |
118 | .spinner {
119 | display:none;
120 | margin-left:auto;
121 | margin-right:auto;
122 | width:21px;
123 | height:21px;
124 | background-image:url('spinner.png');
125 | }
126 |
127 | /* Tools with action links */
128 | .tools-left {
129 | margin-left:10px;
130 | }
131 | .tools-right {
132 | float:right;
133 | margin-right:20px;
134 | }
135 | .tools-right a, .tools-left a {
136 | font-size:10pt;
137 | text-decoration:none;
138 | color:#c0c0c0;
139 | margin-left:15px;
140 | }
141 |
142 | .tools-right a:hover, .tools-left a:hover {
143 | color:#909090;
144 | }
145 |
146 | /* Configuring and displaying the editor window */
147 | .cm-s-default {
148 | border-style:none;
149 | font-size: 11pt !important;
150 | height:auto;
151 | }
152 |
153 | .editor-cm {
154 | width:auto;
155 | height:auto;
156 | max-height:0px;
157 | opacity:0.0;
158 | margin:5px 20px 0px 20px;
159 | transition:max-height 1s;
160 | transition:margin-bottom 1s;
161 | transition:opacity 1.25s;
162 | }
163 |
164 | .editor-cm-visible {
165 | opacity:1.0;
166 | max-height:1000px;
167 | margin-bottom:10px;
168 | }
169 |
170 | /* Side bar with documentation */
171 | #editor-documentation-side {
172 | background:#f8f8f8;
173 | border:1px solid #e0e0e0;
174 | border-radius:5px;
175 | padding:10px;
176 | }
177 | #editor-documentation-side h2 {
178 | font:bold 16pt Rufina,'Times New Roman', Times, serif;
179 | margin-top:0px;
180 | }
181 | #editor-documentation-side p {
182 | font:normal 10pt 'Pontano Sans', sans-serif;
183 | }
184 | #editor-documentation-side dl {
185 | margin:15px 0px 10px 0px;
186 | }
187 | #editor-documentation-side dd {
188 | margin-left: 15px;
189 | }
190 | #editor-documentation-side .map {
191 | padding:10px;
192 | }
193 | #editor-documentation-side pre {
194 | border-style:none;
195 | padding:0px 0px 0px 15px;
196 | color:#3257bb;
197 | }
198 | #editor-documentation-side ul {
199 | margin-left:10px;
200 | }
201 | #editor-documentation-side table {
202 | margin-left:15px;
203 | }
204 | #editor-documentation-side td {
205 | font:normal 10pt 'Pontano Sans', sans-serif;
206 | padding-right:20px;
207 | }
208 |
209 | /****************************** Visualizers *******************************/
210 |
211 | .editor-visual select {
212 | width:100%;
213 | font:normal 11pt 'Pontano Sans', sans-serif;
214 | }
215 |
216 | .editor-visual {
217 | padding:10px 20px 10px 20px;
218 | }
219 |
220 | .editor-visual select, .editor-visual .chosen-container {
221 | margin-bottom:10px;
222 | }
223 |
224 | .editor-visual .chosen-container .chosen-choices
225 | {
226 | border-radius:0px;
227 | padding:3px;
228 | }
229 | .editor-visual .chosen-container-multi .chosen-choices .search-choice {
230 | background:white;
231 | border-style:none;
232 | margin:4px;
233 | box-shadow:none;
234 | float:none;
235 | }
236 |
237 |
238 | /****************************** Normal text formatting *******************************/
239 |
240 | h1 {
241 | font:bold 30pt Rufina,'Times New Roman', Times, serif;
242 | color:black;
243 | }
244 |
245 | h2 {
246 | font:bold 22pt Rufina,'Times New Roman', Times, serif;
247 | color:black;
248 | }
249 |
250 | p {
251 | font:normal 13pt 'Pontano Sans', sans-serif;
252 | }
253 |
254 |
255 | /****************************** Tables *******************************/
256 |
257 | table td, table th {
258 | font:normal 11pt 'Pontano Sans', sans-serif;
259 | }
260 |
261 | table caption {
262 | margin-left:8px;
263 | font:bold 9pt 'Pontano Sans', sans-serif;
264 | text-transform:uppercase;
265 | }
266 |
--------------------------------------------------------------------------------
/web/client/google/codegen.fsx:
--------------------------------------------------------------------------------
1 | // --------------------------------------------------------------------------------------------------------------------
2 | //
3 | // --------------------------------------------------------------------------------------------------------------------
4 |
5 | #load "options.fs"
6 | open System
7 | open System.Reflection
8 | open Microsoft.FSharp.Reflection
9 |
10 | let gc = Assembly.GetExecutingAssembly().GetTypes() |> Seq.find (fun t -> t.Name = "Options")
11 | let types = gc.GetNestedTypes()
12 |
13 | let optionsTypes = types |> Seq.filter (fun t -> t.Name.EndsWith("Options"))
14 | let otherTypes = types |> Seq.filter (fun t -> not (t.Name.EndsWith("Options")))
15 |
16 | let camelCase (name:string) =
17 | name.[0].ToString().ToLower() + name.Substring(1)
18 | let dropSuffixes (name:string) =
19 | name.Replace("ChartOptions", "").Replace("Options", "")
20 |
21 | let primitiveTypeNames =
22 | dict [ typeof, "float"; typeof, "bool"; typeof, "obj"; typeof, "DateTime"
23 | typeof, "string"; typeof, "string[]"; typeof, "float[]"; typeof, "obj[]" ]
24 |
25 | let primitiveTypes =
26 | set [ for t in primitiveTypeNames.Keys -> t.FullName ]
27 |
28 | let getOptions t =
29 | [ for f in FSharpType.GetRecordFields(t) do
30 | let typ = f.PropertyType
31 | let isPrimitive = primitiveTypes.Contains(typ.FullName)
32 | let isNested = FSharpType.IsRecord(typ)
33 | if isPrimitive then yield Choice1Of3(f.Name, typ)
34 | elif isNested then yield Choice2Of3(f.Name, typ)
35 | else yield Choice3Of3(f.Name, typ) ]
36 |
37 | let getAllOptions t =
38 | getOptions t |> List.map (function Choice1Of3 v | Choice2Of3 v | Choice3Of3 v -> v)
39 |
40 | let getPrimitivieNestedOtherOptions t =
41 | let options = getOptions t
42 | options |> List.choose (function Choice1Of3 v -> Some v | _ -> None),
43 | options |> List.choose (function Choice2Of3 v -> Some v | _ -> None),
44 | options |> List.choose (function Choice3Of3 v -> Some v | _ -> None)
45 |
46 | let rec formatInputType (t:System.Type) =
47 | if t.IsArray then "seq<" + (formatInputType (t.GetElementType())) + ">"
48 | elif primitiveTypeNames.ContainsKey(t) then primitiveTypeNames.[t]
49 | else t.Name
50 |
51 | let safeName s = if s = "type" then "``type``" else s
52 |
53 | let formatParameters primitive =
54 | [ for n, t in primitive ->
55 | sprintf "?%s:%s" (safeName n) (formatInputType t) ]
56 | |> String.concat ","
57 |
58 | let getConversion (t:System.Type) =
59 | if t.IsArray then Some("Array.ofSeq")
60 | else None
61 |
62 | let formatSetters primitive =
63 | [ for n, t in primitive ->
64 | let converted =
65 | match getConversion t with
66 | | Some f -> sprintf "(Option.map %s %s)" f (safeName n)
67 | | _ -> n
68 | sprintf "%s = right o \"%s\" %s" (safeName n) n converted ]
69 | |> String.concat "; "
70 |
71 | let formatCopies nested =
72 | [ for n, t in nested ->
73 | sprintf "%s = copy o \"%s\"" n n ]
74 | |> String.concat "; "
75 |
76 | let writeSetters (wr:IO.TextWriter) =
77 | for t in optionsTypes do
78 | let primitive, nested, other = getPrimitivieNestedOtherOptions t
79 | let pars = formatParameters primitive
80 | let sets = formatSetters primitive
81 | fprintfn wr "type %s = " (dropSuffixes t.Name)
82 | fprintfn wr " { data : ChartData; typeName : string; "
83 | fprintfn wr " options : %s }" t.Name
84 | fprintfn wr " interface Chart"
85 | fprintfn wr " member x.show() = Helpers.showChart(x)"
86 | fprintfn wr " member x.set(%s) = " pars
87 | fprintfn wr " let o = x.options"
88 | fprintfn wr " let newOptions = { x.options with %s }" sets
89 | fprintfn wr " { x with options = newOptions }"
90 |
91 | for name, otyp in other do
92 | let pars = formatParameters [name, otyp]
93 | let sets = formatSetters [name, otyp]
94 | fprintfn wr " member x.%s(%s) =" name pars
95 | fprintfn wr " let o = x.options"
96 | fprintfn wr " { x with options = { x.options with %s } }" sets
97 |
98 | for name, ntyp in nested do
99 | let primitive, nested, other = getPrimitivieNestedOtherOptions ntyp
100 | if other <> [] then failwith "!"
101 | let pars = formatParameters primitive
102 | let sets = formatSetters primitive
103 | let copies = formatCopies nested
104 | if pars <> "" then
105 | fprintfn wr " member x.%s(%s) =" name pars
106 | fprintfn wr " let o = x.options.%s" name
107 | fprintfn wr " let newNested = { %s.%s; %s }" ntyp.Name sets copies
108 | fprintfn wr " { x with options = { x.options with %s = newNested } }" name
109 |
110 |
111 | let formatInitializers primitive =
112 | [ for n, t in primitive ->
113 | let converted =
114 | match getConversion t with
115 | | Some f -> sprintf "(Option.map %s %s)" f (safeName n)
116 | | _ -> (safeName n)
117 | sprintf "%s = orDefault %s" (safeName n) converted ]
118 | |> String.concat "; "
119 |
120 | let writeOtherOptions (wr:IO.TextWriter) =
121 | fprintfn wr "type options ="
122 | for t in otherTypes do
123 | let opts = getAllOptions t
124 | let pars = formatParameters opts
125 | let inits = formatInitializers opts
126 | fprintfn wr " static member %s(%s) =" (camelCase t.Name) pars
127 | fprintfn wr " { %s.%s }" t.Name inits
128 |
129 |
130 | let writeChartType (wr:IO.TextWriter) =
131 | for t in optionsTypes do
132 | let opts = [ for n, _ in getAllOptions t -> sprintf "%s = undefined<_>()" n ]
133 | let optsRest = opts |> String.concat "; "
134 |
135 | fprintfn wr "type %s with" t.Name
136 | fprintfn wr " static member empty ="
137 | fprintfn wr " { %s.%s }" t.Name optsRest
138 |
139 |
140 | let write() =
141 | use fs = IO.File.Create(__SOURCE_DIRECTORY__ + "/extensions.fs")
142 | use fw = new IO.StreamWriter(fs)
143 | fprintfn fw "[]"
144 | fprintfn fw "module TheGamma.GoogleCharts.Extensions"
145 | fprintfn fw ""
146 | fprintfn fw "open System"
147 | fprintfn fw "open TheGamma.GoogleCharts"
148 | fprintfn fw "open TheGamma.GoogleCharts.Helpers"
149 | fprintfn fw "open TheGamma.GoogleCharts.Options"
150 | fprintfn fw ""
151 | writeSetters fw
152 | fprintfn fw ""
153 | writeChartType fw
154 | fprintfn fw ""
155 | writeOtherOptions fw
156 |
157 | write()
--------------------------------------------------------------------------------
/data/HtmlProvider.fs:
--------------------------------------------------------------------------------
1 | namespace ProviderImplementation.TheGamma
2 |
3 | open System
4 | open System.Collections.Generic
5 |
6 | open FSharp.Data
7 | open FSharp.Data.Runtime
8 | open FSharp.Data.Runtime.StructuralTypes
9 |
10 | open Microsoft.FSharp.Quotations
11 | open Microsoft.FSharp.Core.CompilerServices
12 | open ProviderImplementation.ProvidedTypes
13 |
14 | // --------------------------------------------------------------------------------------------------------------------
15 | //
16 | // --------------------------------------------------------------------------------------------------------------------
17 |
18 | (*
19 | type JsonGenerationContext =
20 | { TypeProviderType : ProvidedTypeDefinition
21 | UniqueNiceName : string -> string }
22 | static member Create(tpType) =
23 | { TypeProviderType = tpType
24 | UniqueNiceName = NameUtils.uniqueGenerator NameUtils.nicePascalName }
25 |
26 | type GenerationResult =
27 | { ConvertedType : System.Type
28 | Converter : Expr -> Expr }
29 | *)
30 |
31 | module HtmlGenerator =
32 | open TheGamma.Series
33 |
34 | let createTableType (contTy:ProvidedTypeDefinition) (table:HtmlTable) =
35 | let columns = table.InferedProperties.Value
36 |
37 | let tableTy = ProvidedTypeDefinition(table.Name, None, HideObjectMethods = true, NonNullable = true)
38 | let rowTy = ProvidedTypeDefinition(table.Name + " Row", None, HideObjectMethods = true, NonNullable = true)
39 | contTy.AddMember(tableTy)
40 | contTy.AddMember(rowTy)
41 |
42 | for field in columns do
43 | let p = ProvidedProperty(field.Name, rowTy)
44 | p.GetterCode <- fun _ -> <@@ ((failwith "!") : obj) @@>
45 | p |> tableTy.AddMember
46 |
47 | id, typedefof>.MakeGenericType [| typeof; tableTy :> Type |]
48 |
49 |
50 | let createDefinitionListType (t:HtmlDefinitionList) =
51 | id, ProvidedTypeDefinition(t.Name, None, HideObjectMethods = true, NonNullable = true)
52 |
53 |
54 | let createListType (t:HtmlList) =
55 | id, ProvidedTypeDefinition(t.Name, None, HideObjectMethods = true, NonNullable = true)
56 |
57 |
58 | let rec generateHtmlTypes (contTy:ProvidedTypeDefinition) (resTy:ProvidedTypeDefinition) (htmlObjects:HtmlObject list) =
59 | let getPropertyName = NameUtils.uniqueGenerator id
60 |
61 | for htmlObj in htmlObjects do
62 | match htmlObj with
63 | | Table table ->
64 | let create, tableType = createTableType contTy table
65 | resTy.AddMember <| ProvidedProperty(getPropertyName table.Name, tableType, GetterCode = fun (Singleton doc) -> create doc)
66 | | List list ->
67 | let create, tableType = createListType list
68 | contTy.AddMember tableType
69 | resTy.AddMember <| ProvidedProperty(getPropertyName list.Name, tableType, GetterCode = fun (Singleton doc) -> create doc)
70 | | DefinitionList definitionList ->
71 | let create, tableType = createDefinitionListType definitionList
72 | contTy.AddMember tableType
73 | resTy.AddMember <| ProvidedProperty(getPropertyName definitionList.Name, tableType, GetterCode = fun (Singleton doc) -> create doc)
74 |
75 | // --------------------------------------------------------------------------------------------------------------------
76 | //
77 | // --------------------------------------------------------------------------------------------------------------------
78 |
79 | []
80 | type public Html(cfg:TypeProviderConfig) as this =
81 | inherit TypeProviderForNamespaces()
82 |
83 | let asm = System.Reflection.Assembly.GetExecutingAssembly()
84 | let ns = "TheGamma"
85 | let iniType = ProvidedTypeDefinition(asm, ns, "html", Some(typeof))
86 | let parameter = ProvidedStaticParameter("sample", typeof)
87 |
88 | do iniType.DefineStaticParameters([parameter], fun typeName args ->
89 |
90 | // Read the JSON sample and run the type inference on it
91 | let sample =
92 | let value = args.[0] :?> string
93 | try Async.RunSynchronously(Cache.asyncDownload (Uri(value).ToString()))
94 | with _ -> args.[0] :?> string
95 |
96 | let unitsOfMeasureProvider =
97 | { new StructuralInference.IUnitsOfMeasureProvider with
98 | member x.SI(str) = ProvidedMeasureBuilder.Default.SI str
99 | member x.Product(measure1, measure2) = ProvidedMeasureBuilder.Default.Product(measure1, measure2)
100 | member x.Inverse(denominator): Type = ProvidedMeasureBuilder.Default.Inverse(denominator) }
101 |
102 | let inferenceParameters : HtmlInference.Parameters =
103 | { MissingValues = TextRuntime.GetMissingValues ""
104 | CultureInfo = System.Globalization.CultureInfo.InvariantCulture
105 | UnitsOfMeasureProvider = unitsOfMeasureProvider
106 | PreferOptionals = true }
107 |
108 | let htmlType =
109 | HtmlDocument.Parse sample
110 | |> HtmlRuntime.getHtmlObjects (Some inferenceParameters) false
111 | |> List.map (function
112 | | Table table when table.InferedProperties = None ->
113 | let ip =
114 | HtmlInference.inferColumns
115 | inferenceParameters
116 | table.HeaderNamesAndUnits.Value
117 | (if table.HasHeaders.Value then table.Rows.[1..] else table.Rows)
118 | Table { table with InferedProperties = Some ip }
119 | | html -> html)
120 |
121 | //|> HtmlGenerator.generateTypes asm ns typeName (inferenceParameters, missingValuesStr, cultureStr) replacer
122 |
123 | //
124 | let resTy = ProvidedTypeDefinition(asm, ns, typeName, Some typeof, HideObjectMethods = true)
125 | let contTy = ProvidedTypeDefinition("Types", None)
126 | contTy.AddXmlDoc("[OMIT]")
127 | resTy.AddMember(contTy)
128 | //let ctx = JsonGenerationContext.Create(resTy)
129 | HtmlGenerator.generateHtmlTypes contTy resTy htmlType
130 |
131 | let loadM =
132 | ProvidedMethod
133 | ( "read", [], resTy,
134 | IsStaticMethod = true, InvokeCode = fun (Singleton arg) ->
135 | <@@ JS.Json.parseJson(%%arg) @@> )
136 | let parseM =
137 | ProvidedMethod
138 | ( "parse", [ProvidedParameter("json", typeof)], resTy,
139 | IsStaticMethod = true, InvokeCode = fun (Singleton arg) ->
140 | <@@ JS.Json.parseJson(%%arg) @@> )
141 | resTy.AddMembers [parseM; loadM]
142 | resTy)
143 |
144 |
145 | // Register the main (parameterized) type with F# compiler
146 | do this.AddNamespace(ns, [ iniType ])
147 |
148 | []
149 | do()
--------------------------------------------------------------------------------
/web/web/scripts/codemirror/mode/fsharp.js:
--------------------------------------------------------------------------------
1 | CodeMirror.defineMode('fsharp', function ()
2 | {
3 | var words = {
4 | 'abstract': 'keyword',
5 | 'and': 'keyword',
6 | 'as': 'keyword',
7 | 'assert': 'keyword',
8 | 'base': 'keyword',
9 | 'begin': 'keyword',
10 | 'class': 'keyword',
11 | 'default': 'keyword',
12 | 'delegate': 'keyword',
13 | 'do': 'keyword',
14 | 'done': 'keyword',
15 | 'downcast': 'keyword',
16 | 'downto': 'keyword',
17 | 'elif': 'keyword',
18 | 'else': 'keyword',
19 | 'end': 'keyword',
20 | 'exception': 'keyword',
21 | 'extern': 'keyword',
22 | 'false': 'keyword',
23 | 'finally': 'keyword',
24 | 'for': 'keyword',
25 | 'fun': 'keyword',
26 | 'function': 'keyword',
27 | 'fun': 'keyword',
28 | 'global': 'keyword',
29 | 'if': 'keyword',
30 | 'in': 'keyword',
31 | 'inherit': 'keyword',
32 | 'inline': 'keyword',
33 | 'interface': 'keyword',
34 | 'internal': 'keyword',
35 | 'lazy': 'keyword',
36 | 'let': 'keyword',
37 | 'let!': 'keyword',
38 | 'match': 'keyword',
39 | 'member': 'keyword',
40 | 'module': 'keyword',
41 | 'mutable': 'keyword',
42 | 'namespace': 'keyword',
43 | 'new': 'keyword',
44 | 'not': 'keyword',
45 | 'null': 'keyword',
46 | 'of': 'keyword',
47 | 'open': 'keyword',
48 | 'or': 'keyword',
49 | 'override': 'keyword',
50 | 'private': 'keyword',
51 | 'public': 'keyword',
52 | 'rec': 'keyword',
53 | 'return': 'keyword',
54 | 'return!': 'keyword',
55 | 'select': 'keyword',
56 | 'static': 'keyword',
57 | 'struct': 'keyword',
58 | 'then': 'keyword',
59 | 'to': 'keyword',
60 | 'true': 'keyword',
61 | 'try': 'keyword',
62 | 'type': 'keyword',
63 | 'upcast': 'keyword',
64 | 'use': 'keyword',
65 | 'use!': 'keyword',
66 | 'val': 'keyword',
67 | 'void': 'keyword',
68 | 'when': 'keyword',
69 | 'while': 'keyword',
70 | 'with': 'keyword',
71 | 'yield': 'keyword',
72 | 'yield!': 'keyword',
73 | '__SOURCE_DIRECTORY__': 'keyword',
74 | 'asr': 'keyword',
75 | 'land': 'keyword',
76 | 'lor': 'keyword',
77 | 'lsl': 'keyword',
78 | 'lsr': 'keyword',
79 | 'lxor': 'keyword',
80 | 'mod': 'keyword',
81 | 'sig': 'keyword',
82 | 'atomic': 'keyword',
83 | 'break': 'keyword',
84 | 'checked': 'keyword',
85 | 'component': 'keyword',
86 | 'const': 'keyword',
87 | 'constraint': 'keyword',
88 | 'constructor': 'keyword',
89 | 'continue': 'keyword',
90 | 'eager': 'keyword',
91 | 'event': 'keyword',
92 | 'external': 'keyword',
93 | 'fixed': 'keyword',
94 | 'functor': 'keyword',
95 | 'include': 'keyword',
96 | 'method': 'keyword',
97 | 'mixin': 'keyword',
98 | 'object': 'keyword',
99 | 'parallel': 'keyword',
100 | 'process': 'keyword',
101 | 'protected': 'keyword',
102 | 'pure': 'keyword',
103 | 'sealed': 'keyword',
104 | 'tailcall': 'keyword',
105 | 'trait': 'keyword',
106 | 'virtual': 'keyword',
107 | 'volatile': 'keyword'
108 | };
109 |
110 | function tokenBase(stream, state)
111 | {
112 | var ch = stream.next();
113 |
114 | if (ch === '"')
115 | {
116 | state.tokenize = tokenString;
117 | return state.tokenize(stream, state);
118 | }
119 | if (ch === '/')
120 | {
121 | if (stream.eat('/')) {
122 | stream.eatWhile(/[^\n\r]/);
123 | return 'comment';
124 | }
125 | }
126 | if (ch === '(')
127 | {
128 | if (stream.eat('*'))
129 | {
130 | state.commentLevel++;
131 | state.tokenize = tokenComment;
132 | return state.tokenize(stream, state);
133 | }
134 | }
135 | if (ch === '~')
136 | {
137 | stream.eatWhile(/\w/);
138 | return 'variable-2';
139 | }
140 | if (ch === '`')
141 | {
142 | stream.next();
143 | stream.next();
144 | stream.eatWhile(/[^`]/);
145 | stream.next();
146 | stream.next();
147 | return 'variable';
148 | }
149 | if (/\d/.test(ch))
150 | {
151 | stream.eatWhile(/[\d]/);
152 | if (stream.eat('.'))
153 | {
154 | stream.eatWhile(/[\d]/);
155 | }
156 | return 'number';
157 | }
158 | if (/[+\-*&%=<>!?|]/.test(ch))
159 | {
160 | return 'operator';
161 | }
162 | stream.eatWhile(/\w/);
163 | var cur = stream.current();
164 | return words[cur] || 'variable';
165 | }
166 |
167 | function tokenString(stream, state)
168 | {
169 | var next, end = false, escaped = false;
170 | while ((next = stream.next()) != null)
171 | {
172 | if (next === '"' && !escaped)
173 | {
174 | end = true;
175 | break;
176 | }
177 | escaped = !escaped && next === '\\';
178 | }
179 | if (end && !escaped)
180 | {
181 | state.tokenize = tokenBase;
182 | }
183 | return 'string';
184 | }
185 |
186 | function tokenComment(stream, state)
187 | {
188 | var prev, next;
189 | while (state.commentLevel > 0 && (next = stream.next()) != null)
190 | {
191 | if (prev === '(' && next === '*') state.commentLevel++;
192 | if (prev === '*' && next === ')') state.commentLevel--;
193 | prev = next;
194 | }
195 | if (state.commentLevel <= 0)
196 | {
197 | state.tokenize = tokenBase;
198 | }
199 | return 'comment';
200 | }
201 |
202 | return {
203 | startState: function () { return { tokenize: tokenBase, commentLevel: 0 }; },
204 | token: function (stream, state)
205 | {
206 | if (stream.eatSpace()) return null;
207 | return state.tokenize(stream, state);
208 | },
209 |
210 | blockCommentStart: "(*",
211 | blockCommentEnd: "*)"
212 | };
213 | });
214 |
215 | CodeMirror.defineMIME("text/x-fsharp", "fsharp");
--------------------------------------------------------------------------------
/web/demos/us-states.md:
--------------------------------------------------------------------------------
1 | What countries do US states look like?
2 | ======================================
3 |
4 | Select a US state:
5 |
63 |
64 |
68 |
69 |
70 |
71 |
79 |
80 |
81 |
124 |
127 |
128 |
129 |
130 | ## Most similar countries in the world
131 |
132 | Given a US state, what are the most similar countries in the world based on the population and area of the state?
133 |
134 |
135 |
136 |
137 | | Country | Population | Area |
138 |
139 |
140 |
141 |
142 |
143 |
144 |
145 |
--------------------------------------------------------------------------------
/web/web/content/codemirror.css:
--------------------------------------------------------------------------------
1 | /* BASICS */
2 |
3 | .CodeMirror {
4 | /* Set height, width, borders, and global font properties here */
5 | font-family: Monaco, Menlo, 'Ubuntu Mono', Consolas, source-code-pro, monospace;
6 | font-size: 12px;
7 | height: 300px;
8 | border: 1px solid black;
9 | }
10 | .CodeMirror-scroll {
11 | /* Set scrolling behaviour here */
12 | overflow: auto;
13 | }
14 |
15 | /* PADDING */
16 |
17 | .CodeMirror-lines {
18 | padding: 4px 0; /* Vertical padding around content */
19 | }
20 | .CodeMirror pre {
21 | padding: 0 4px; /* Horizontal padding of content */
22 | }
23 |
24 | .CodeMirror-scrollbar-filler, .CodeMirror-gutter-filler {
25 | background-color: white; /* The little square between H and V scrollbars */
26 | }
27 |
28 | /* GUTTER */
29 |
30 | .CodeMirror-gutters {
31 | border-right: 1px solid #ddd;
32 | background-color: #f7f7f7;
33 | white-space: nowrap;
34 | }
35 | .CodeMirror-linenumbers {}
36 | .CodeMirror-linenumber {
37 | padding: 0 3px 0 5px;
38 | min-width: 20px;
39 | text-align: right;
40 | color: #999;
41 | }
42 |
43 | /* CURSOR */
44 |
45 | .CodeMirror div.CodeMirror-cursor {
46 | border-left: 1px solid black;
47 | z-index: 3;
48 | }
49 | /* Shown when moving in bi-directional text */
50 | .CodeMirror div.CodeMirror-secondarycursor {
51 | border-left: 1px solid silver;
52 | }
53 | .CodeMirror.cm-keymap-fat-cursor div.CodeMirror-cursor {
54 | width: auto;
55 | border: 0;
56 | background: #7e7;
57 | z-index: 1;
58 | }
59 | /* Can style cursor different in overwrite (non-insert) mode */
60 | .CodeMirror div.CodeMirror-cursor.CodeMirror-overwrite {}
61 |
62 | .cm-tab { display: inline-block; }
63 |
64 | /* DEFAULT THEME */
65 |
66 | .cm-s-default .cm-keyword {color: #708;}
67 | .cm-s-default .cm-atom {color: #219;}
68 | .cm-s-default .cm-number {color: #164;}
69 | .cm-s-default .cm-def {color: #00f;}
70 | .cm-s-default .cm-variable {color: black;}
71 | .cm-s-default .cm-variable-2 {color: #05a;}
72 | .cm-s-default .cm-variable-3 {color: #085;}
73 | .cm-s-default .cm-property {color: black;}
74 | .cm-s-default .cm-operator {color: black;}
75 | .cm-s-default .cm-comment {color: #a50;}
76 | .cm-s-default .cm-string {color: #a11;}
77 | .cm-s-default .cm-string-2 {color: #f50;}
78 | .cm-s-default .cm-meta {color: #555;}
79 | .cm-s-default .cm-qualifier {color: #555;}
80 | .cm-s-default .cm-builtin {color: #30a;}
81 | .cm-s-default .cm-bracket {color: #997;}
82 | .cm-s-default .cm-tag {color: #170;}
83 | .cm-s-default .cm-attribute {color: #00c;}
84 | .cm-s-default .cm-header {color: blue;}
85 | .cm-s-default .cm-quote {color: #090;}
86 | .cm-s-default .cm-hr {color: #999;}
87 | .cm-s-default .cm-link {color: #00c;}
88 |
89 | .cm-negative {color: #d44;}
90 | .cm-positive {color: #292;}
91 | .cm-header, .cm-strong {font-weight: bold;}
92 | .cm-em {font-style: italic;}
93 | .cm-link {text-decoration: underline;}
94 |
95 | .cm-s-default .cm-error {color: #f00;}
96 | .cm-invalidchar {color: #f00;}
97 |
98 | div.CodeMirror span.CodeMirror-matchingbracket {color: #0f0;}
99 | div.CodeMirror span.CodeMirror-nonmatchingbracket {color: #f22;}
100 | .CodeMirror-activeline-background {background: #e8f2ff;}
101 |
102 | /* STOP */
103 |
104 | /* The rest of this file contains styles related to the mechanics of
105 | the editor. You probably shouldn't touch them. */
106 |
107 | .CodeMirror {
108 | line-height: 1;
109 | position: relative;
110 | overflow: hidden;
111 | background: white;
112 | color: black;
113 | }
114 |
115 | .CodeMirror-scroll {
116 | /* 30px is the magic margin used to hide the element's real scrollbars */
117 | /* See overflow: hidden in .CodeMirror */
118 | margin-bottom: -30px; margin-right: -30px;
119 | padding-bottom: 30px; padding-right: 30px;
120 | height: 100%;
121 | outline: none; /* Prevent dragging from highlighting the element */
122 | position: relative;
123 | -moz-box-sizing: content-box;
124 | box-sizing: content-box;
125 | }
126 | .CodeMirror-sizer {
127 | position: relative;
128 | }
129 |
130 | /* The fake, visible scrollbars. Used to force redraw during scrolling
131 | before actuall scrolling happens, thus preventing shaking and
132 | flickering artifacts. */
133 | .CodeMirror-vscrollbar, .CodeMirror-hscrollbar, .CodeMirror-scrollbar-filler, .CodeMirror-gutter-filler {
134 | position: absolute;
135 | z-index: 6;
136 | display: none;
137 | }
138 | .CodeMirror-vscrollbar {
139 | right: 0; top: 0;
140 | overflow-x: hidden;
141 | overflow-y: scroll;
142 | }
143 | .CodeMirror-hscrollbar {
144 | bottom: 0; left: 0;
145 | overflow-y: hidden;
146 | overflow-x: scroll;
147 | }
148 | .CodeMirror-scrollbar-filler {
149 | right: 0; bottom: 0;
150 | }
151 | .CodeMirror-gutter-filler {
152 | left: 0; bottom: 0;
153 | }
154 |
155 | .CodeMirror-gutters {
156 | position: absolute; left: 0; top: 0;
157 | padding-bottom: 30px;
158 | z-index: 3;
159 | }
160 | .CodeMirror-gutter {
161 | white-space: normal;
162 | height: 100%;
163 | -moz-box-sizing: content-box;
164 | box-sizing: content-box;
165 | padding-bottom: 30px;
166 | margin-bottom: -32px;
167 | display: inline-block;
168 | /* Hack to make IE7 behave */
169 | *zoom:1;
170 | *display:inline;
171 | }
172 | .CodeMirror-gutter-elt {
173 | position: absolute;
174 | cursor: default;
175 | z-index: 4;
176 | }
177 |
178 | .CodeMirror-lines {
179 | cursor: text;
180 | }
181 | .CodeMirror pre {
182 | /* Reset some styles that the rest of the page might have set */
183 | -moz-border-radius: 0; -webkit-border-radius: 0; border-radius: 0;
184 | border-width: 0;
185 | background: transparent;
186 | font-family: inherit;
187 | font-size: inherit;
188 | margin: 0;
189 | white-space: pre;
190 | word-wrap: normal;
191 | line-height: inherit;
192 | color: inherit;
193 | z-index: 2;
194 | position: relative;
195 | overflow: visible;
196 | }
197 | .CodeMirror-wrap pre {
198 | word-wrap: break-word;
199 | white-space: pre-wrap;
200 | word-break: normal;
201 | }
202 | .CodeMirror-code pre {
203 | border-right: 30px solid transparent;
204 | width: -webkit-fit-content;
205 | width: -moz-fit-content;
206 | width: fit-content;
207 | }
208 | .CodeMirror-wrap .CodeMirror-code pre {
209 | border-right: none;
210 | width: auto;
211 | }
212 | .CodeMirror-linebackground {
213 | position: absolute;
214 | left: 0; right: 0; top: 0; bottom: 0;
215 | z-index: 0;
216 | }
217 |
218 | .CodeMirror-linewidget {
219 | position: relative;
220 | z-index: 2;
221 | overflow: auto;
222 | }
223 |
224 | .CodeMirror-widget {}
225 |
226 | .CodeMirror-wrap .CodeMirror-scroll {
227 | overflow-x: hidden;
228 | }
229 |
230 | .CodeMirror-measure {
231 | position: absolute;
232 | width: 100%;
233 | height: 0;
234 | overflow: hidden;
235 | visibility: hidden;
236 | }
237 | .CodeMirror-measure pre { position: static; }
238 |
239 | .CodeMirror div.CodeMirror-cursor {
240 | position: absolute;
241 | visibility: hidden;
242 | border-right: none;
243 | width: 0;
244 | }
245 | .CodeMirror-focused div.CodeMirror-cursor {
246 | visibility: visible;
247 | }
248 |
249 | .CodeMirror-selected { background: #d9d9d9; }
250 | .CodeMirror-focused .CodeMirror-selected { background: #d7d4f0; }
251 |
252 | .cm-searching {
253 | background: #ffa;
254 | background: rgba(255, 255, 0, .4);
255 | }
256 |
257 | /* IE7 hack to prevent it from returning funny offsetTops on the spans */
258 | .CodeMirror span { *vertical-align: text-bottom; }
259 |
260 | @media print {
261 | /* Hide the cursor when printing */
262 | .CodeMirror div.CodeMirror-cursor {
263 | visibility: hidden;
264 | }
265 | }
266 |
--------------------------------------------------------------------------------
/data/TheGamma.Html.fsproj:
--------------------------------------------------------------------------------
1 |
2 |
3 |
4 |
5 | Debug
6 | AnyCPU
7 | 2.0
8 | {7c4d0059-950e-48bc-b32e-1eb3ec4c1901}
9 | Library
10 | TheGamma.Data
11 | TheGamma.Html
12 | v4.5
13 | 4.3.1.0
14 | TheGamma.Html
15 |
16 |
17 | true
18 | full
19 | false
20 | false
21 | bin\Debug\
22 | DEBUG;TRACE
23 | 3
24 | bin\Debug\TheGamma.Html.XML
25 |
26 |
27 | pdbonly
28 | true
29 | true
30 | bin\Release\
31 | TRACE
32 | 3
33 | bin\Release\TheGamma.Data.XML
34 |
35 |
36 | 11
37 |
38 |
39 |
40 |
41 | $(MSBuildExtensionsPath32)\..\Microsoft SDKs\F#\3.0\Framework\v4.0\Microsoft.FSharp.Targets
42 |
43 |
44 |
45 |
46 | $(MSBuildExtensionsPath32)\Microsoft\VisualStudio\v$(VisualStudioVersion)\FSharp\Microsoft.FSharp.Targets
47 |
48 |
49 |
50 |
51 |
58 |
59 |
60 |
61 |
62 |
63 |
64 |
65 | lib\FunScript.dll
66 |
67 |
68 | lib\FunScript.Interop.dll
69 |
70 |
71 | lib\FunScript.TypeScript.Binding.lib.dll
72 |
73 |
74 |
75 | False
76 |
77 |
78 |
79 |
80 |
81 |
82 |
83 | TheGamma.Data
84 | {5f6a630c-3068-4835-82e9-fa670d6db0a6}
85 | True
86 |
87 |
88 |
89 |
90 |
91 |
92 |
93 |
94 |
95 |
96 | packages\FSharp.Data\lib\portable-net40+sl5+wp8+win8\FSharp.Data.dll
97 | True
98 | True
99 |
100 |
101 |
102 |
103 |
104 |
105 | packages\FSharp.Data\lib\net40\FSharp.Data.dll
106 | True
107 | True
108 |
109 |
110 | True
111 |
112 |
113 |
114 |
115 |
116 |
117 |
118 |
119 | packages\Zlib.Portable\lib\portable-net4+sl5+wp8+win8+wpa81+MonoTouch+MonoAndroid\Zlib.Portable.dll
120 | True
121 | True
122 |
123 |
124 |
125 |
126 |
--------------------------------------------------------------------------------
/data/TheGamma.Json.fsproj:
--------------------------------------------------------------------------------
1 |
2 |
3 |
4 |
5 | Debug
6 | AnyCPU
7 | 2.0
8 | 01423b98-b2aa-4378-bd66-1b27c1a2b5f4
9 | Library
10 | TheGamma.Data
11 | TheGamma.Json
12 | v4.5
13 | 4.3.1.0
14 | TheGamma.Json
15 |
16 |
17 | true
18 | full
19 | false
20 | false
21 | bin\Debug\
22 | DEBUG;TRACE
23 | 3
24 | bin\Debug\TheGamma.Json.XML
25 |
26 |
27 | pdbonly
28 | true
29 | true
30 | bin\Release\
31 | TRACE
32 | 3
33 | bin\Release\TheGamma.Data.XML
34 |
35 |
36 | 11
37 |
38 |
39 |
40 |
41 | $(MSBuildExtensionsPath32)\..\Microsoft SDKs\F#\3.0\Framework\v4.0\Microsoft.FSharp.Targets
42 |
43 |
44 |
45 |
46 | $(MSBuildExtensionsPath32)\Microsoft\VisualStudio\v$(VisualStudioVersion)\FSharp\Microsoft.FSharp.Targets
47 |
48 |
49 |
50 |
51 |
58 |
59 |
60 |
61 |
62 |
63 |
64 |
65 | lib\FunScript.dll
66 |
67 |
68 | lib\FunScript.Interop.dll
69 |
70 |
71 | lib\FunScript.TypeScript.Binding.lib.dll
72 |
73 |
74 |
75 | False
76 |
77 |
78 |
79 |
80 |
81 |
82 |
83 | TheGamma.Data
84 | {5f6a630c-3068-4835-82e9-fa670d6db0a6}
85 | True
86 |
87 |
88 |
89 |
90 |
91 |
92 |
93 |
94 |
95 |
96 | packages\FSharp.Data\lib\portable-net40+sl5+wp8+win8\FSharp.Data.dll
97 | True
98 | True
99 |
100 |
101 |
102 |
103 |
104 |
105 | packages\FSharp.Data\lib\net40\FSharp.Data.dll
106 | True
107 | True
108 |
109 |
110 | True
111 |
112 |
113 |
114 |
115 |
116 |
117 |
118 |
119 | packages\Zlib.Portable\lib\portable-net4+sl5+wp8+win8+wpa81+MonoTouch+MonoAndroid\Zlib.Portable.dll
120 | True
121 | True
122 |
123 |
124 |
125 |
126 |
--------------------------------------------------------------------------------
/data/TheGamma.World.fsproj:
--------------------------------------------------------------------------------
1 |
2 |
3 |
4 |
5 | Debug
6 | AnyCPU
7 | 2.0
8 | {179d2573-f6fc-43d3-8dfd-57c1a62ef4b2}
9 | Library
10 | TheGamma.Data
11 | TheGamma.World
12 | v4.5
13 | 4.3.1.0
14 | TheGamma.World
15 |
16 |
17 | true
18 | full
19 | false
20 | false
21 | bin\Debug\
22 | DEBUG;TRACE
23 | 3
24 | bin\Debug\TheGamma.World.XML
25 |
26 |
27 | pdbonly
28 | true
29 | true
30 | bin\Release\
31 | TRACE
32 | 3
33 | bin\Release\TheGamma.Data.XML
34 |
35 |
36 | 11
37 |
38 |
39 |
40 |
41 | $(MSBuildExtensionsPath32)\..\Microsoft SDKs\F#\3.0\Framework\v4.0\Microsoft.FSharp.Targets
42 |
43 |
44 |
45 |
46 | $(MSBuildExtensionsPath32)\Microsoft\VisualStudio\v$(VisualStudioVersion)\FSharp\Microsoft.FSharp.Targets
47 |
48 |
49 |
50 |
51 |
58 |
59 |
60 |
61 |
62 |
63 |
64 |
65 | lib\FunScript.dll
66 |
67 |
68 | lib\FunScript.Interop.dll
69 |
70 |
71 | lib\FunScript.TypeScript.Binding.lib.dll
72 |
73 |
74 |
75 | False
76 |
77 |
78 |
79 |
80 |
81 |
82 |
83 |
84 | TheGamma.Data
85 | {5f6a630c-3068-4835-82e9-fa670d6db0a6}
86 | True
87 |
88 |
89 | TheGamma.Json
90 | {01423b98-b2aa-4378-bd66-1b27c1a2b5f4}
91 | True
92 |
93 |
94 |
95 |
96 |
97 |
98 |
99 |
100 |
101 |
102 | packages\FSharp.Data\lib\portable-net40+sl5+wp8+win8\FSharp.Data.dll
103 | True
104 | True
105 |
106 |
107 |
108 |
109 |
110 |
111 | packages\FSharp.Data\lib\net40\FSharp.Data.dll
112 | True
113 | True
114 |
115 |
116 | True
117 |
118 |
119 |
120 |
121 |
122 |
123 |
124 |
125 | packages\Zlib.Portable\lib\portable-net4+sl5+wp8+win8+wpa81+MonoTouch+MonoAndroid\Zlib.Portable.dll
126 | True
127 | True
128 |
129 |
130 |
131 |
132 |
--------------------------------------------------------------------------------
/data/TheGamma.Data.fsproj:
--------------------------------------------------------------------------------
1 |
2 |
3 |
4 |
5 | Debug
6 | AnyCPU
7 | 2.0
8 | {5f6a630c-3068-4835-82e9-fa670d6db0a6}
9 | Library
10 | TheGamma.Data
11 | TheGamma.Data
12 | v4.5
13 | 4.3.1.0
14 | TheGamma.Data
15 |
16 |
17 | true
18 | full
19 | false
20 | false
21 | bin\Debug\
22 | DEBUG;TRACE
23 | 3
24 | bin\Debug\TheGamma.Data.XML
25 |
26 |
27 | pdbonly
28 | true
29 | true
30 | bin\Release\
31 | TRACE
32 | 3
33 | bin\Release\TheGamma.Data.XML
34 |
35 |
36 | 11
37 |
38 |
39 |
40 |
41 | $(MSBuildExtensionsPath32)\..\Microsoft SDKs\F#\3.0\Framework\v4.0\Microsoft.FSharp.Targets
42 |
43 |
44 |
45 |
46 | $(MSBuildExtensionsPath32)\Microsoft\VisualStudio\v$(VisualStudioVersion)\FSharp\Microsoft.FSharp.Targets
47 |
48 |
49 |
50 |
51 |
58 |
59 |
60 | True
61 | paket-files/ProvidedTypes.fsi
62 |
63 |
64 | True
65 | paket-files/ProvidedTypes.fs
66 |
67 |
68 | True
69 | paket-files/DebugProvidedTypes.fs
70 |
71 |
72 |
73 |
74 |
75 |
76 | lib\FunScript.dll
77 |
78 |
79 | lib\FunScript.Interop.dll
80 |
81 |
82 | lib\FunScript.TypeScript.Binding.lib.dll
83 |
84 |
85 |
86 | False
87 |
88 |
89 |
90 |
91 |
92 |
93 |
94 |
95 |
96 |
97 |
98 |
99 |
100 | packages\FSharp.Data\lib\portable-net40+sl5+wp8+win8\FSharp.Data.dll
101 | True
102 | True
103 |
104 |
105 |
106 |
107 |
108 |
109 | packages\FSharp.Data\lib\net40\FSharp.Data.dll
110 | True
111 | True
112 |
113 |
114 | True
115 |
116 |
117 |
118 |
119 |
120 |
121 |
122 |
123 | packages\Zlib.Portable\lib\portable-net4+sl5+wp8+win8+wpa81+MonoTouch+MonoAndroid\Zlib.Portable.dll
124 | True
125 | True
126 |
127 |
128 |
129 |
130 |
--------------------------------------------------------------------------------
/web/client/series.fs:
--------------------------------------------------------------------------------
1 | namespace TheGamma.Series
2 |
3 | open FunScript
4 |
5 | // --------------------------------------------------------------------------------------------------------------------
6 | // Series helpers - various JavaScript functions needed for simple series implementation
7 | // --------------------------------------------------------------------------------------------------------------------
8 |
9 | []
10 | module SeriesInternals =
11 | open System.Collections.Generic
12 |
13 | []
14 | let isNull(o:obj) : bool = failwith "never"
15 |
16 | []
17 | let getProperty<'T> (obj:obj) (name:string) : 'T = failwith "never"
18 |
19 | []
20 | let compare (x:'a) (y:'a) : int = failwith "never"
21 |
22 | let slice lo hi (arr:'T[]) =
23 | Array.init (hi - lo + 1) (fun i -> arr.[lo + i])
24 |
25 | let dictAny (v:seq<'k*'v>) = unbox> (dict (unbox> v))
26 |
27 | let zipUnsorted (arr1:_[]) (arr2:_[]) =
28 | let d1 = dictAny arr1
29 | let d2 = dictAny arr2
30 | let res = ResizeArray<_>()
31 | for kv1 in d1 do
32 | let v2 =
33 | if d2.ContainsKey(kv1.Key) then Some(d2.[kv1.Key])
34 | else None
35 | res.Add(kv1.Key, (Some kv1.Value, v2))
36 | for kv2 in d2 do
37 | if not (d1.ContainsKey(kv2.Key)) then
38 | res.Add(kv2.Key, (None, Some kv2.Value))
39 | Array.ofSeq res
40 |
41 | let isSortedUsing test proj (arr:_[]) =
42 | let rec loop i =
43 | if i = arr.Length then true
44 | else test (proj arr.[i-1]) (proj arr.[i]) && loop (i+1)
45 | arr.Length = 0 || loop 1
46 |
47 | let zipSorted (arr1:('k*'v1)[]) (arr2:('k*'v2)[]) =
48 | let mutable i1 = 0
49 | let mutable i2 = 0
50 | let inline (<.) (a:'k) (b:'k) = compare a b < 0
51 | let inline eq (a:'k) (b:'k) = compare a b = 0
52 | let res = ResizeArray<_>()
53 | while i1 < arr1.Length && i2 < arr2.Length do
54 | let (k1, v1), (k2, v2) = arr1.[i1], arr2.[i2]
55 | if eq k1 k2 then
56 | res.Add(k1, (Some v1, Some v2))
57 | i1 <- i1 + 1
58 | i2 <- i2 + 1
59 | elif k1 <. k2 then
60 | res.Add(k1, (Some v1, None))
61 | i1 <- i1 + 1
62 | elif k2 <. k1 then
63 | res.Add(k2, (None, Some v2))
64 | i2 <- i2 + 1
65 | while i1 < arr1.Length do
66 | let k1, v1 = arr1.[i1]
67 | res.Add(k1, (Some v1, None))
68 | i1 <- i1 + 1
69 | while i2 < arr2.Length do
70 | let k2, v2 = arr2.[i2]
71 | res.Add(k2, (None, Some v2))
72 | i2 <- i2 + 2
73 | Array.ofSeq res
74 |
75 | let zipAny (arr1:('k*'v1)[]) (arr2:('k*'v2)[]) =
76 | let inline (<=.) (a:'k) (b:'k) = compare a b <= 0
77 | let inline (>=.) (a:'k) (b:'k) = compare a b >= 0
78 | if isSortedUsing (<=.) fst arr1 && isSortedUsing (<=.) fst arr2 then zipSorted arr1 arr2
79 | elif isSortedUsing (>=.) fst arr1 && isSortedUsing (>=.) fst arr2 then Array.rev (zipSorted (Array.rev arr1) (Array.rev arr2))
80 | else zipUnsorted arr1 arr2
81 |
82 | // --------------------------------------------------------------------------------------------------------------------
83 | // Async series library for TheGamma - implements type `series<'k, 'v>` with various operations
84 | // --------------------------------------------------------------------------------------------------------------------
85 |
86 | open SeriesInternals
87 | open TheGamma.Series
88 |
89 | type value<'k> = { value : Async<'k> }
90 |
91 | []
92 | module Operations =
93 | let inline lift f (s:series<_, _>) =
94 | s.set(async {
95 | let! vs = s.data
96 | return f vs })
97 |
98 | let inline liftAggregation f (s:series<_, _>) =
99 | { value = async {
100 | let! vs = s.data
101 | return f vs } }
102 |
103 | type series<'k, 'v> with
104 | member s.sortKeys(?reverse) =
105 | s |> lift (fun arr ->
106 | arr |> Array.sortWith (fun (k1, _) (k2, _) -> compare k1 k2)
107 | |> (if reverse = Some true then Array.rev else id))
108 |
109 | member s.sortValues(?reverse) =
110 | s |> lift (fun arr ->
111 | arr |> Array.sortWith (fun (_,v1) (_,v2) -> compare v1 v2)
112 | |> (if reverse = Some true then Array.rev else id))
113 |
114 | member s.sortBy(f, ?reverse) =
115 | s |> lift (fun arr ->
116 | arr |> Array.sortWith (fun (_,v1) (_,v2) -> compare (f v1) (f v2))
117 | |> (if reverse = Some true then Array.rev else id))
118 |
119 | member s.reverse() =
120 | s |> lift (Array.rev)
121 |
122 | member s.take(count) =
123 | s |> lift (fun arr -> slice 0 ((min arr.Length count)-1) arr)
124 |
125 | member s.skip(count) =
126 | s |> lift (fun arr -> slice (min arr.Length count) (arr.Length-1) arr)
127 |
128 | member s.map(f) =
129 | s |> lift (Array.map (fun (k, v) -> k, f v))
130 |
131 | member s.mapTask(f:'v -> value<'r>) =
132 | s.set(async {
133 | let! arr = s.data
134 | let res = Array.init arr.Length (fun _ -> None)
135 | for i in 0 .. arr.Length-1 do
136 | let! r = (f(snd arr.[i])).value
137 | res.[i] <- Some r
138 | return Array.init arr.Length (fun i -> fst arr.[i], res.[i].Value)
139 | })
140 |
141 | member s.mapPairs(f) =
142 | s |> lift (Array.map (fun (k, v) -> k, f k v))
143 |
144 | member s.filter(f) =
145 | s |> lift (Array.filter (snd >> f))
146 |
147 | member s.choose(f) =
148 | s |> lift (Array.choose (fun (k, v) -> match f v with None -> None | Some r -> Some(k, r)))
149 |
150 | member s.joinOuter<'v2>(s2:series<'k, 'v2>) : series<'k, 'v option * 'v2 option>=
151 | let data = async {
152 | let! v1 = s.data
153 | let! v2 = s2.data
154 | return zipAny v1 v2 }
155 | series.create(data, s.keyName, "Values", s.seriesName + " and " + s2.seriesName)
156 |
157 | member s.joinInner<'v2>(s2:series<'k, 'v2>) : series<'k, 'v * 'v2>=
158 | s.joinOuter(s2).choose(function Some(v1), Some(v2) -> Some((v1, v2)) | _ -> None)
159 |
160 | []
161 | member s.append(key:'k, value:'v) =
162 | s |> lift (fun arr -> Array.append arr [| key, value |])
163 |
164 | []
165 | member s.append(key:'k, value:value<'v>) =
166 | s.set(async {
167 | let! arr = s.data
168 | let! v = value.value
169 | return Array.append arr [| key, v |] })
170 |
171 | member s.append(s2:series<'k, 'v>) =
172 | s.set(async {
173 | let! arr1 = s.data
174 | let! arr2 = s2.data
175 | return Array.append arr1 arr2 })
176 |
177 | member s.last() =
178 | s |> liftAggregation (fun arr -> snd arr.[arr.Length - 1])
179 |
180 | member s.first() =
181 | s |> liftAggregation (fun arr -> snd arr.[0])
182 |
183 | member s.minBy(f) =
184 | s |> liftAggregation (Array.minBy (fun (k, v) -> f v))
185 |
186 | member s.maxBy(f) =
187 | s |> liftAggregation (Array.maxBy (fun (k, v) -> f v))
188 |
189 | open System.Runtime.CompilerServices
190 |
191 | []
192 | type SeriesExtensions =
193 | []
194 | static member sum(s:series<'k, float>) =
195 | s |> liftAggregation (Array.sumBy snd)
196 |
197 | []
198 | static member series(values:seq<'v>) =
199 | let getKey i (v:'v) =
200 | let name = getProperty v "name"
201 | let id = getProperty v "id"
202 | if not (isNull name) then name
203 | elif not (isNull id) then id
204 | else string i
205 | let data = async { return values |> Array.ofSeq |> Array.mapi (fun i v -> getKey i v, v) }
206 | series.create(data, "Key", "Value", "Series")
207 |
208 | []
209 | static member series(values:list<'v>) =
210 | SeriesExtensions.series(values :> seq<_>)
211 |
212 | []
213 | type ListExtensions =
214 | []
215 | static member map(list, f) = List.map f list
216 |
217 | []
218 | type TupleExtensions =
219 | []
220 | static member map((a,b), f) = (f a, f b)
221 | []
222 | static member map((a,b,c), f) = (f a, f b, f c)
223 | []
224 | static member map((a,b,c,d), f) = (f a, f b, f c, f d)
225 | []
226 | static member map((a,b,c,d,e), f) = (f a, f b, f c, f d, f e)
227 | []
228 | static member map((a,b,c,d,e,g), f) = (f a, f b, f c, f d, f e, f g)
229 | []
230 | static member map((a,b,c,d,e,g,h), f) = (f a, f b, f c, f d, f e, f g, f h)
231 |
--------------------------------------------------------------------------------
/web/web/content/editor.css:
--------------------------------------------------------------------------------
1 | .br-intellisense {
2 | min-width: 220px;
3 | max-height: 176px;
4 | min-height: 22px;
5 | z-index: 10;
6 | overflow: auto;
7 | position: absolute;
8 | background-color: white;
9 | border: 1px solid #E5C365;
10 | box-shadow: 2px 3px 5px rgba(0, 0, 0, .2);
11 | padding: 0;
12 | margin: 5px;
13 | display: none;
14 | }
15 | .br-documentation {
16 | min-width: 200px;
17 | padding: 3px;
18 | overflow: auto;
19 | position: absolute;
20 | z-index: 10;
21 | background-color: #E7E8EC;
22 | border: 1px solid #CCCEDB;
23 | box-shadow: 2px 3px 5px rgba(0,0,0,.2);
24 | font-family: 'Segoe UI';
25 | font-size: 10pt;
26 | display: none;
27 | }
28 | .br-listlink {
29 | font-family: 'Segoe UI';
30 | font-size: 10pt;
31 | list-style: none;
32 | cursor: pointer;
33 | border: 1px solid white;
34 | white-space: nowrap;
35 | overflow: hidden;
36 | }
37 | .br-listlink:hover {
38 | background-color: #FDF4BF;
39 | }
40 | .br-selected {
41 | background-color: #FDF4BF;
42 | border: 1px dotted black;
43 | }
44 | .br-icon {
45 | width: 16px;
46 | height: 16px;
47 | display: inline-block;
48 | vertical-align: text-top;
49 | margin: 2px;
50 | }
51 | .br-methods {
52 | min-width: 220px;
53 | min-height: 22px;
54 | z-index: 10;
55 | padding: 3px;
56 | overflow: auto;
57 | position: absolute;
58 | background-color: #E7E8EC;
59 | border: 1px solid #CCCEDB;
60 | margin: 5px;
61 | display: none;
62 | font-family: 'Segoe UI';
63 | font-size: 10pt;
64 | }
65 | .br-methods-text {
66 | margin-left: 75px;
67 | }
68 | .br-methods-arrows {
69 | width: 75px;
70 | float: left;
71 | font-family: Calibri;
72 | font-weight: bold;
73 | -webkit-touch-callout: none;
74 | -webkit-user-select: none;
75 | -moz-user-select: none;
76 | -ms-user-select: none;
77 | user-select: none;
78 | }
79 | .br-methods-arrow {
80 | cursor: pointer;
81 | }
82 | .br-methods-arrow-text {
83 | font-weight: normal;
84 | margin-left: 2px;
85 | margin-right: 2px;
86 | }
87 |
88 | .icon-glyph-72 {
89 | background-image: url('glyphs/method.png');
90 | }
91 |
92 | .icon-glyph-74 {
93 | background-image: url('glyphs/static-method.png');
94 | }
95 |
96 | .icon-glyph-102 {
97 | background-image: url('glyphs/property.png');
98 | }
99 |
100 | .icon-glyph-42 {
101 | background-image: url('glyphs/property.png');
102 | }
103 |
104 | .icon-glyph-6 {
105 | background-image: url('glyphs/static-property.png');
106 | }
107 |
108 | .icon-glyph-90 {
109 | background-image: url('glyphs/namespace.png');
110 | }
111 |
112 | .icon-glyph-120 {
113 | background-image: url('glyphs/class.png');
114 | }
115 |
116 | .icon-glyph-84 {
117 | background-image: url('glyphs/class.png');
118 | }
119 |
120 | .icon-glyph-0 {
121 | background-image: url('glyphs/class.png');
122 | }
123 |
124 | .icon-glyph-48 {
125 | background-image: url('glyphs/interface.png');
126 | }
127 |
128 | .icon-glyph-12 {
129 | background-image: url('glyphs/delegate.png');
130 | }
131 |
132 | .icon-glyph-108 {
133 | background-image: url('glyphs/struct.png');
134 | }
135 |
136 | .icon-glyph-18 {
137 | background-image: url('glyphs/enum.png');
138 | }
139 |
140 | .icon-glyph-30 {
141 | background-image: url('glyphs/event.png');
142 | }
143 |
144 | .type {
145 | color: #003ca7;
146 | }
147 |
148 | #cssmenu ul,
149 | #cssmenu li,
150 | #cssmenu span,
151 | #cssmenu a {
152 | margin: 0;
153 | padding: 0;
154 | position: relative;
155 | }
156 | #cssmenu {
157 | height: 49px;
158 | border-radius: 5px 5px 0 0;
159 | -moz-border-radius: 5px 5px 0 0;
160 | -webkit-border-radius: 5px 5px 0 0;
161 | background: #fefefe;
162 | background: -moz-linear-gradient(top, #fefefe 0%, #eee9f0 100%);
163 | background: -webkit-gradient(linear, left top, left bottom, color-stop(0%, #fefefe), color-stop(100%, #eee9f0));
164 | background: -webkit-linear-gradient(top, #fefefe 0%, #eee9f0 100%);
165 | background: -o-linear-gradient(top, #fefefe 0%, #eee9f0 100%);
166 | background: -ms-linear-gradient(top, #fefefe 0%, #eee9f0 100%);
167 | background: linear-gradient(top, #fefefe 0%, #eee9f0 100%);
168 | border-bottom: 2px solid #8747ff;
169 | width: auto;
170 | }
171 | #cssmenu:after,
172 | #cssmenu ul:after {
173 | content: '';
174 | display: block;
175 | clear: both;
176 | }
177 | #cssmenu a {
178 | background: #fefefe;
179 | background: -moz-linear-gradient(top, #fefefe 0%, #ececec 100%);
180 | background: -webkit-gradient(linear, left top, left bottom, color-stop(0%, #fefefe), color-stop(100%, #ececec));
181 | background: -webkit-linear-gradient(top, #fefefe 0%, #ececec 100%);
182 | background: -o-linear-gradient(top, #fefefe 0%, #ececec 100%);
183 | background: -ms-linear-gradient(top, #fefefe 0%, #ececec 100%);
184 | background: linear-gradient(top, #fefefe 0%, #ececec 100%);
185 | color: #000;
186 | display: inline-block;
187 | font-family: Helvetica, Arial, Verdana, sans-serif;
188 | font-size: 12px;
189 | line-height: 49px;
190 | padding: 0 20px;
191 | text-decoration: none;
192 | }
193 | #cssmenu ul {
194 | list-style: none;
195 | }
196 | #cssmenu > ul {
197 | float: left;
198 | }
199 | #cssmenu > ul > li {
200 | float: left;
201 | }
202 | #cssmenu > ul > li > a {
203 | color: #000;
204 | font-size: 12px;
205 | }
206 | #cssmenu > ul > li:hover:after {
207 | content: '';
208 | display: block;
209 | width: 0;
210 | height: 0;
211 | position: absolute;
212 | left: 50%;
213 | bottom: 0;
214 | border-left: 10px solid transparent;
215 | border-right: 10px solid transparent;
216 | border-bottom: 10px solid #8747ff;
217 | margin-left: -10px;
218 | }
219 | #cssmenu > ul > li:first-child > a {
220 | border-radius: 5px 0 0 0;
221 | -moz-border-radius: 5px 0 0 0;
222 | -webkit-border-radius: 5px 0 0 0;
223 | }
224 | #cssmenu > ul > li.active:after {
225 | content: '';
226 | display: block;
227 | width: 0;
228 | height: 0;
229 | position: absolute;
230 | left: 50%;
231 | bottom: 0;
232 | border-left: 10px solid transparent;
233 | border-right: 10px solid transparent;
234 | border-bottom: 10px solid #8747ff;
235 | margin-left: -10px;
236 | }
237 | #cssmenu > ul > li.active > a {
238 | -moz-box-shadow: inset 0 0 2px rgba(0, 0, 0, 0.1);
239 | -webkit-box-shadow: inset 0 0 2px rgba(0, 0, 0, 0.1);
240 | box-shadow: inset 0 0 2px rgba(0, 0, 0, 0.1);
241 | background: #ececec;
242 | background: -moz-linear-gradient(top, #ececec 0%, #ffeeff ef 100%);
243 | background: -webkit-gradient(linear, left top, left bottom, color-stop(0%, #ececec), color-stop(100%, #ffeeff ef));
244 | background: -webkit-linear-gradient(top, #ececec 0%, #ffeeff ef 100%);
245 | background: -o-linear-gradient(top, #ececec 0%, #ffeeff ef 100%);
246 | background: -ms-linear-gradient(top, #ececec 0%, #ffeeff ef 100%);
247 | background: linear-gradient(top, #ececec 0%, #ffeeff ef 100%);
248 | }
249 | #cssmenu > ul > li:hover > a {
250 | background: #ececec;
251 | background: -moz-linear-gradient(top, #ececec 0%, #ffeeff ef 100%);
252 | background: -webkit-gradient(linear, left top, left bottom, color-stop(0%, #ececec), color-stop(100%, #ffeeff ef));
253 | background: -webkit-linear-gradient(top, #ececec 0%, #ffeeff ef 100%);
254 | background: -o-linear-gradient(top, #ececec 0%, #ffeeff ef 100%);
255 | background: -ms-linear-gradient(top, #ececec 0%, #ffeeff ef 100%);
256 | background: linear-gradient(top, #ececec 0%, #ffeeff ef 100%);
257 | -moz-box-shadow: inset 0 0 2px rgba(0, 0, 0, 0.1);
258 | -webkit-box-shadow: inset 0 0 2px rgba(0, 0, 0, 0.1);
259 | box-shadow: inset 0 0 2px rgba(0, 0, 0, 0.1);
260 | }
261 | #cssmenu .has-sub {
262 | z-index: 1;
263 | }
264 | #cssmenu .has-sub:hover > ul {
265 | display: block;
266 | }
267 | #cssmenu .has-sub ul {
268 | display: none;
269 | position: absolute;
270 | width: 200px;
271 | top: 100%;
272 | left: 0;
273 | }
274 | #cssmenu .has-sub ul li {
275 | *margin-bottom: -1px;
276 | }
277 | #cssmenu .has-sub ul li a {
278 | background: #8747ff;
279 | border-bottom: 1px dotted #a87aff;
280 | filter: none;
281 | font-size: 11px;
282 | display: block;
283 | line-height: 120%;
284 | padding: 10px;
285 | color: #ffffff;
286 | }
287 | #cssmenu .has-sub ul li:hover a {
288 | background: #6614ff;
289 | }
290 | #cssmenu .has-sub .has-sub:hover > ul {
291 | display: block;
292 | }
293 | #cssmenu .has-sub .has-sub ul {
294 | display: none;
295 | position: absolute;
296 | left: 100%;
297 | top: 0;
298 | }
299 | #cssmenu .has-sub .has-sub ul li a {
300 | background: #6614ff;
301 | border-bottom: 1px dotted #a87aff;
302 | }
303 | #cssmenu .has-sub .has-sub ul li a:hover {
304 | background: #5700f9;
305 | }
306 |
--------------------------------------------------------------------------------
/web/web/scripts/codemirror/codemirror-intellisense.js:
--------------------------------------------------------------------------------
1 | var Intellisense = function (editor, userCallback, methodsCallback)
2 | {
3 | var utils = new Utils();
4 | var decls = new DeclarationsIntellisense();
5 | var meths = new MethodsIntellisense();
6 | var autoCompleteStart = { lineIndex: 0, columnIndex: 0 };
7 |
8 | /**
9 | * Inserts the currently selected auto complete
10 | */
11 | function insertAutoComplete()
12 | {
13 | if (decls.isVisible())
14 | {
15 | var selectedDeclaration = decls.getSelectedItem();
16 | var cursor = editor.getCursor();
17 | var line = editor.getLine(autoCompleteStart.lineIndex);
18 | var name = selectedDeclaration.name;
19 | if (!isNaN(name[0]) || utils.lastIndexOfAny(name, [' ', '[', ']', '.']) != -1)
20 | {
21 | name = '``' + name + '``';
22 | }
23 |
24 | // Find the end of the current token. If we're inside backtick, try to find end of backtick
25 | // otherwise, find end of a token (whitespace or things like that)
26 | var endCh = cursor.ch;
27 | if (line[autoCompleteStart.columnIndex] == '`' && line[autoCompleteStart.columnIndex + 1] == '`') {
28 | while (endCh < line.length && line[endCh] != '`') endCh++;
29 | if (line[endCh] == '`') endCh++;
30 | if (line[endCh] == '`') endCh++;
31 | }
32 | else {
33 | while (endCh < line.length && line[endCh].match(/[a-zA-Z0-9]/) != null) endCh++;
34 | }
35 |
36 | var startRange = { line: cursor.line, ch: autoCompleteStart.columnIndex };
37 | var endRange = { line: cursor.line, ch: endCh };
38 | editor.replaceRange(name, startRange, endRange);
39 | editor.setSelection({ line: cursor.line, ch: autoCompleteStart.columnIndex + name.length});
40 | decls.setVisible(false);
41 | editor.focus();
42 | }
43 | };
44 |
45 | /**
46 | * Sets the declarations and repositions the declarations UI.
47 | */
48 | function setDeclarations(data)
49 | {
50 | var coords = editor.cursorCoords(true, 'page');
51 | decls.setDeclarations(data);
52 | decls.setPosition(coords.left, coords.bottom);
53 | meths.setVisible(false);
54 |
55 | // Filter the declaratons based on the current word
56 | var cursor = editor.getCursor();
57 | var line = editor.doc.getLine(autoCompleteStart.lineIndex);
58 | var filterText = line.substring(autoCompleteStart.columnIndex, editor.getCursor().ch).toLowerCase()
59 | decls.setFilter(filterText);
60 | }
61 |
62 | /**
63 | * Sets the methods and repositions the methods UI.
64 | */
65 | function setMethods(data)
66 | {
67 | var coords = editor.cursorCoords(true, 'page');
68 | meths.setMethods(data);
69 | meths.setPosition(coords.left, coords.bottom);
70 | decls.setVisible(false);
71 | }
72 |
73 | /**
74 | * Requests that the user provide items to display in the intellisense popup
75 | */
76 | function autoComplete()
77 | {
78 | if (typeof (userCallback) === 'function')
79 | {
80 | var cursor = editor.doc.getCursor();
81 | var line = editor.doc.getLine(cursor.line);
82 | var find = utils.lastIndexOfAny(line, [' ', '\t', '.'], cursor.ch) + 1;
83 | autoCompleteStart = { lineIndex: cursor.line, columnIndex: find };
84 | userCallback(autoCompleteStart, setDeclarations);
85 | }
86 | };
87 |
88 | /**
89 | * Requests that the user provide items to display in the methods popup
90 | */
91 | function autoCompleteMethods()
92 | {
93 | if (typeof (methodsCallback) === 'function')
94 | {
95 | var cursor = editor.getCursor();
96 | autoCompleteStart = { lineIndex: cursor.line, columnIndex: cursor.ch };
97 | methodsCallback(autoCompleteStart, setMethods);
98 | }
99 | };
100 |
101 | /**
102 | * Check to see if the cursor is to the left of where we started showing it
103 | */
104 | function isMethodsOff()
105 | {
106 | var cursor = editor.getCursor();
107 | return (cursor.ch <= autoCompleteStart.columnIndex);
108 | }
109 |
110 | /**
111 | * When the document changes, update the UI when certain events occur
112 | */
113 | editor.doc.on('change', function (cm, changes)
114 | {
115 | if (decls.isVisible() && (changes.origin === '+delete' || changes.origin === '+input'))
116 | {
117 | var cursor = editor.getCursor();
118 | if (cursor.ch <= autoCompleteStart.columnIndex)
119 | {
120 | decls.setVisible(false);
121 | meths.setVisible(false);
122 | }
123 | else
124 | {
125 | var line = editor.doc.getLine(autoCompleteStart.lineIndex);
126 | var filterText = line.substring(autoCompleteStart.columnIndex, editor.getCursor().ch).toLowerCase()
127 | decls.setFilter(filterText);
128 | }
129 | }
130 | else if (meths.isVisible() && (changes.origin === '+delete' || changes.origin === '+input'))
131 | {
132 | meths.setVisible(!isMethodsOff());
133 | }
134 | });
135 |
136 | editor.on('keydown', function (cm, evt)
137 | {
138 | if (evt.keyCode === 27)
139 | {
140 | meths.setVisible(false);
141 | decls.setVisible(false);
142 | }
143 |
144 | if (meths.isVisible())
145 | {
146 | // left
147 | if (evt.keyCode === 37)
148 | {
149 | meths.setVisible(!isMethodsOff());
150 | }
151 | // up
152 | else if (evt.keyCode === 38)
153 | {
154 | meths.moveSelected(-1);
155 | evt.preventDefault();
156 | }
157 | // down
158 | else if (evt.keyCode === 40)
159 | {
160 | meths.moveSelected(1);
161 | evt.preventDefault();
162 | }
163 | // right paren
164 | else if (evt.shiftKey && evt.keyCode === 48)
165 | {
166 | meths.setVisible(false);
167 | }
168 | }
169 | else if (decls.isVisible())
170 | {
171 | // escape, left, right
172 | if (evt.keyCode === 37 || evt.keyCode === 39)
173 | {
174 | decls.setVisible(false);
175 | }
176 | // up
177 | else if (evt.keyCode === 38)
178 | {
179 | decls.moveSelected(-1);
180 | evt.preventDefault();
181 | }
182 | // down
183 | else if (evt.keyCode === 40)
184 | {
185 | decls.moveSelected(1);
186 | evt.preventDefault();
187 | }
188 | // page down
189 | else if (evt.keyCode === 34)
190 | {
191 | decls.moveSelected(5);
192 | evt.preventDefault();
193 | }
194 | // page up
195 | else if (evt.keyCode === 33)
196 | {
197 | decls.moveSelected(-5);
198 | evt.preventDefault();
199 | }
200 | // tab
201 | else if (evt.keyCode === 9)
202 | {
203 | insertAutoComplete();
204 | evt.preventDefault();
205 | }
206 | // enter
207 | else if (evt.keyCode === 13)
208 | {
209 | insertAutoComplete();
210 | evt.preventDefault();
211 | }
212 | else if (evt.shiftKey && evt.keyCode === 57)
213 | {
214 | // left paren, right after we finished typing name
215 | decls.setVisible(false);
216 | autoCompleteMethods();
217 | }
218 |
219 | }
220 | else if (evt.shiftKey)
221 | {
222 | // left paren
223 | if (evt.keyCode === 57)
224 | {
225 | autoCompleteMethods();
226 | }
227 | }
228 | });
229 |
230 | editor.addKeyMap({
231 | 'Ctrl-Space': function (cm)
232 | {
233 | autoComplete();
234 | },
235 | '.': function (cm)
236 | {
237 | cm.replaceSelection('.', "end", "+input");
238 | autoComplete();
239 | }
240 | });
241 |
242 | // when the user chooses an item, insert it
243 | decls.onItemChosen(insertAutoComplete);
244 |
245 | // public API
246 | this.setMethods = setMethods;
247 | this.setDeclarations = setDeclarations;
248 | };
--------------------------------------------------------------------------------
/web/code/editor.fs:
--------------------------------------------------------------------------------
1 | module TheGamma.Server.Editor
2 |
3 | open Microsoft.FSharp.Compiler.SourceCodeServices
4 | open Microsoft.FSharp.Compiler.Interactive.Shell
5 | open Microsoft.FSharp.Compiler.Ast
6 | open System.Text
7 | open System.IO
8 |
9 | open TheGamma.Server.Common
10 |
11 | // ------------------------------------------------------------------------------------------------
12 | // F# compiler service wrapper
13 | // ------------------------------------------------------------------------------------------------
14 |
15 | /// Extracts all consecutive identifiers to the left of the charIndex for a specified line of code
16 | let extractIdentTokens line charIndex =
17 | let sourceTok = SourceTokenizer([], "/home/test.fsx")
18 | let tokenizer = sourceTok.CreateLineTokenizer(line)
19 |
20 | let rec gatherTokens (tokenizer:FSharpLineTokenizer) state = seq {
21 | match tokenizer.ScanToken(state) with
22 | | Some tok, state ->
23 | yield tok
24 | yield! gatherTokens tokenizer state
25 | | None, state -> () }
26 |
27 | let tokens = gatherTokens tokenizer 0L |> Seq.toArray
28 | let idx = tokens |> Array.tryFindIndex(fun x ->
29 | charIndex > x.LeftColumn && charIndex <= x.LeftColumn + x.FullMatchedLength)
30 |
31 | match idx with
32 | | Some(endIndex) ->
33 | let startIndex =
34 | tokens.[0..endIndex]
35 | |> Array.rev
36 | |> Array.tryFindIndex (fun x -> x.TokenName <> "IDENT" && x.TokenName <> "DOT")
37 | |> Option.map (fun x -> endIndex - x)
38 | let startIndex = defaultArg startIndex 0
39 | let idents = tokens.[startIndex..endIndex] |> Array.filter (fun x -> x.TokenName = "IDENT")
40 | Some tokens.[endIndex], idents
41 |
42 | | None -> None, Array.empty
43 |
44 | /// Parses the line of F# code and builds a list of identifier names in order
45 | /// to be passed into the `GetDeclarations`, `GetMethods`, or other functions
46 | ///
47 | /// For tooltips and overlodas, set identOffset=0; For completion set identOffset=1
48 | let extractNames line charIndex identOffset =
49 | let charToken, tokens = extractIdentTokens line charIndex
50 | match charToken with
51 | | None -> 0, 0, []
52 | | Some(charToken) ->
53 | let names = tokens |> Array.map (fun x ->
54 | line.Substring(x.LeftColumn, x.FullMatchedLength).Trim('`'))
55 | let takeSize = tokens.Length - identOffset
56 | let finalList =
57 | if charToken.TokenName = "IDENT" && Array.length(tokens) > takeSize then
58 | names |> Seq.take takeSize |> Seq.toList
59 | else
60 | names |> Seq.toList
61 | (charToken.LeftColumn, charToken.LeftColumn + charToken.FullMatchedLength, finalList)
62 |
63 | // Mostly boring code to format tooltips reported from method overloads
64 | let htmlEncode (s:string) = s.Trim().Replace("&", "&").Replace("<", "<").Replace(">", ">")
65 | let formatComment cmt (sb:StringBuilder) =
66 | match cmt with
67 | | FSharpXmlDoc.Text(s) -> sb.AppendLine(s.Trim()) |> ignore
68 | | FSharpXmlDoc.XmlDocFileSignature(file, signature) -> ()
69 | | FSharpXmlDoc.None -> ()
70 | let formatTipElement isSingle el (sbSig:StringBuilder) (sbText:StringBuilder) =
71 | match el with
72 | | FSharpToolTipElement.None -> ()
73 | | FSharpToolTipElement.Single(it, comment) ->
74 | sbSig.AppendLine(htmlEncode it) |> ignore
75 | formatComment comment sbText
76 | | FSharpToolTipElement.Group(items) ->
77 | let items, msg =
78 | if items.Length > 10 then
79 | (items |> Seq.take 10 |> List.ofSeq),
80 | sprintf " (+%d other overloads)" (items.Length - 10)
81 | else items, ""
82 | if isSingle && items.Length > 1 then
83 | sbSig.AppendLine("Multiple overloads") |> ignore
84 | for (it, comment) in items do
85 | sbSig.AppendLine(it) |> ignore
86 | formatComment comment sbText
87 | if msg <> null then sbSig.AppendFormat(msg) |> ignore
88 | | FSharpToolTipElement.CompositionError(err) ->
89 | sbText.Append("Composition error: " + err) |> ignore
90 | let formatTip tip =
91 | let sbSig = StringBuilder()
92 | let sbText = StringBuilder()
93 | match tip with
94 | | FSharpToolTipText([single]) -> formatTipElement true single sbSig sbText
95 | | FSharpToolTipText(its) -> for item in its do formatTipElement false item sbSig sbText
96 | sbSig.ToString().Trim('\n', '\r'),
97 | sbText.ToString().Trim('\n', '\r')
98 |
99 | /// Check specified file and return parsing & type checking results
100 | let checkFile (fileName, source) (checker:FSharpChecker) = async {
101 | let! options = checker.GetProjectOptionsFromScript(fileName, source)
102 | match checker.TryGetRecentTypeCheckResultsForFile(fileName, options, source) with
103 | | Some(parse, check, _) -> return parse, check
104 | | None ->
105 | let! parse = checker.ParseFileInProject(fileName, source, options)
106 | let! answer = checker.CheckFileInProject(parse, fileName, 0, source, options)
107 | match answer with
108 | | FSharpCheckFileAnswer.Succeeded(check) -> return parse, check
109 | | FSharpCheckFileAnswer.Aborted -> return failwith "Parsing did not finish" }
110 |
111 | /// Get declarations (completion) at the specified line & column (lines are 1-based)
112 | let getDeclarations (fileName, source) (line, col) (checker:FSharpChecker) = async {
113 | let! parse, check = checkFile (fileName, source) checker
114 | let textLine = getLines(source).[line-1]
115 | let _, _, names = extractNames textLine col 1
116 | printfn "Names: %A" names
117 | let! decls = check.GetDeclarationListInfo(Some parse, line, col, textLine, names, "")
118 | return [ for it in decls.Items -> it.Name, it.Glyph, formatTip it.DescriptionText ] }
119 |
120 | /// Get method overloads (for the method before '('). Lines are 1-based
121 | let getMethodOverloads (fileName, source) (line, col) (checker:FSharpChecker) = async {
122 | let! parse, check = checkFile (fileName, source) checker
123 | let textLine = getLines(source).[line-1]
124 | match extractNames textLine col 0 with
125 | | _, _, [] -> return List.empty
126 | | _, _, names ->
127 | let! methods = check.GetMethodsAlternate(line, col, textLine, Some names)
128 | return [ for m in methods.Methods -> formatTip m.Description ] }
129 |
130 | // ------------------------------------------------------------------------------------------------
131 | // Suave.io web server
132 | // ------------------------------------------------------------------------------------------------
133 |
134 | open System
135 | open Suave
136 | open Suave.Web
137 | open Suave.Http
138 | open Suave.Types
139 | open FSharp.Data
140 |
141 | /// Types of JSON values that we are returning from F# Compiler Service calls
142 | type JsonTypes = JsonProvider<"""{
143 | "declarations":
144 | {"declarations":[ {"name":"Method", "glyph":1, "signature":"Text", "documentation":"Text"} ]},
145 | "errors":
146 | {"errors":[ {"startLine":1, "startColumn":1, "endLine":1, "endColumn":1, "message":"error"} ]},
147 | "methods":
148 | {"methods":[ "first info", "second info" ] }
149 | }""">
150 |
151 | // This script is implicitly inserted before every source code we get
152 | let loadScript =
153 | [| "#load \"load.fsx\"\n"
154 | "open TheGamma\n"
155 | "open TheGamma.Series\n"
156 | "open TheGamma.GoogleCharts\n" |]
157 |
158 | let loadScriptString =
159 | String.Concat(loadScript)
160 |
161 | /// The main handler for Suave server!
162 | let webPart (checker:ResourceAgent) ctx = async {
163 | match ctx.request.url.LocalPath, getRequestParams ctx with
164 |
165 | // Type-check the source code & return list with error information
166 | | "/check", (_, _, source) ->
167 | let! _, check =
168 | checkFile (Config.scriptFile, loadScriptString + source)
169 | |> checker.Process
170 | let res =
171 | [| for err in check.Errors ->
172 | JsonTypes.Error
173 | ( err.StartLineAlternate-1-loadScript.Length, err.StartColumn,
174 | err.EndLineAlternate-1-loadScript.Length, err.EndColumn, err.Message ) |]
175 | return! ctx |> noCacheSuccess (JsonTypes.Errors(res).JsonValue.ToString())
176 |
177 | // Get method overloads & parameter info at the specified location in the source
178 | | "/methods", (Some line, Some col, source) ->
179 | printfn "Get method overloads: %d,%d" line col
180 | let! meths =
181 | getMethodOverloads (Config.scriptFile, loadScriptString + source)
182 | (line + loadScript.Length, col)
183 | |> checker.Process
184 | let res = JsonTypes.Methods(Array.ofSeq (Seq.map (fun (s1, s2) -> s1 + s2) meths))
185 | return! ctx |> noCacheSuccess (res.JsonValue.ToString())
186 |
187 | // Get auto-completion for the specified location
188 | | "/declarations", (Some line, Some col, source) ->
189 | printfn "Get declarations: %d,%d" line col
190 | let! decls =
191 | getDeclarations (Config.scriptFile, loadScriptString + source)
192 | (line + loadScript.Length, col)
193 | |> checker.Process
194 | decls |> Seq.iter (fun (n,g,_) -> printfn " - %s (%d)" n g)
195 | let res =
196 | [| for name, glyph, (sg, info) in decls do
197 | if not (info.Contains("[OMIT]")) then
198 | yield JsonTypes.Declaration(name, glyph, sg, info) |]
199 | return! ctx |> noCacheSuccess (JsonTypes.Declarations(res).JsonValue.ToString())
200 |
201 | | _ -> return None }
202 |
--------------------------------------------------------------------------------