From ab89ad007ed49e3a99ced592a67ad26e5cbe1850 Mon Sep 17 00:00:00 2001 From: Thomas Honeyman Date: Tue, 25 May 2021 10:18:45 -0700 Subject: [PATCH 01/12] Support loading examples from GitHub repositories --- client/config/dev/Try.Config.purs | 4 +-- client/config/prod/Try.Config.purs | 4 +-- client/examples/Main.purs | 57 ++++++++++++++++++++++++++++++ client/spago.dhall | 2 +- client/src/Try/Container.purs | 34 ++++++++++++------ client/src/Try/GitHub.purs | 20 +++++++++++ 6 files changed, 106 insertions(+), 15 deletions(-) create mode 100644 client/examples/Main.purs create mode 100644 client/src/Try/GitHub.purs diff --git a/client/config/dev/Try.Config.purs b/client/config/dev/Try.Config.purs index 5c6218f1..fcd92ee3 100644 --- a/client/config/dev/Try.Config.purs +++ b/client/config/dev/Try.Config.purs @@ -6,5 +6,5 @@ loaderUrl = "js/output" compileUrl :: String compileUrl = "http://localhost:8081" -mainGist :: String -mainGist = "7ad2b2eef11ac7dcfd14aa1585dd8f69" +mainGitHubExample :: String +mainGitHubExample = "purescript/trypurescript/master/client/examples/Main.purs" diff --git a/client/config/prod/Try.Config.purs b/client/config/prod/Try.Config.purs index e2232d10..726346dc 100644 --- a/client/config/prod/Try.Config.purs +++ b/client/config/prod/Try.Config.purs @@ -6,5 +6,5 @@ loaderUrl = "https://compile.purescript.org/output" compileUrl :: String compileUrl = "https://compile.purescript.org" -mainGist :: String -mainGist = "7ad2b2eef11ac7dcfd14aa1585dd8f69" +mainGitHubExample :: String +mainGitHubExample = "purescript/trypurescript/master/client/examples/Main.purs" diff --git a/client/examples/Main.purs b/client/examples/Main.purs new file mode 100644 index 00000000..9723626e --- /dev/null +++ b/client/examples/Main.purs @@ -0,0 +1,57 @@ +module Main where + +import Prelude + +import Effect (Effect) +import Data.Foldable (fold) +import TryPureScript (h1, h2, p, text, list, indent, link, render, code) + +main :: Effect Unit +main = + render $ fold + [ h1 (text "Try PureScript!") + , p (text "Try out the examples below, or create your own!") + , h2 (text "Examples") + , list (map fromExample examples) + , h2 (text "Share Your Code") + , p (text "Code can be loaded from a GitHub Gist. To share code, simply include the Gist ID in the URL as follows:") + , indent (p (code (text " try.purescript.org?gist=gist-id"))) + , p (fold + [ text "The Gist should contain a file named " + , code (text "Main.purs") + , text " containing your PureScript code." + ]) + ] + where + fromExample { title, gist } = + link ("https://gist.github.com/" <> gist) (text title) + + examples = + [ { title: "Algebraic Data Types" + , gist: "387999a4467a39744ece236e69a442ec" + } + , { title: "Loops" + , gist: "429eab1e957e807f9feeddbf4f573dd0" + } + , { title: "Operators" + , gist: "8395d2b421a5ca6d1056e301a6e12599" + } + , { title: "Records" + , gist: "170c3ca22f0141ed06a120a12b8243af" + } + , { title: "Recursion" + , gist: "659ae8a085f1cf6e52fed2c35ad93643" + } + , { title: "Do Notation" + , gist: "525cb36c147d3497f652028db1214ec8" + } + , { title: "Type Classes" + , gist: "b04463fd49cd4d7d385941b3b2fa226a" + } + , { title: "Generic Programming" + , gist: "e3b6284959f65ac674d39aa981fcb8fb" + } + , { title: "QuickCheck" + , gist: "69f7f94fe4ff3bd47f4b" + } + ] diff --git a/client/spago.dhall b/client/spago.dhall index d8c65090..9d1c9531 100644 --- a/client/spago.dhall +++ b/client/spago.dhall @@ -41,5 +41,5 @@ , "web-html" ] , packages = ./packages.dhall -, sources = [ "src/**/*.purs", "test/**/*.purs" ] +, sources = [ "src/**/*.purs", "test/**/*.purs", "../staging/src/**/*.purs" ] } diff --git a/client/src/Try/Container.purs b/client/src/Try/Container.purs index 69caa46a..35c447b6 100644 --- a/client/src/Try/Container.purs +++ b/client/src/Try/Container.purs @@ -7,7 +7,7 @@ import Control.Monad.Except (runExceptT) import Data.Array (fold) import Data.Array as Array import Data.Either (Either(..), hush) -import Data.Foldable (for_) +import Data.Foldable (for_, oneOf) import Data.FoldableWithIndex (foldMapWithIndex) import Data.Maybe (Maybe(..), fromMaybe, isNothing) import Data.Symbol (SProxy(..)) @@ -27,6 +27,7 @@ import Try.Config as Config import Try.Editor (MarkerType(..), toStringMarkerType) import Try.Editor as Editor import Try.Gist (getGistById, tryLoadFileFromGist) +import Try.GitHub (getRawGitHubFile) import Try.Loader (Loader, makeLoader, runLoader) import Try.QueryString (getQueryStringMaybe) import Try.Session (createSessionIdIfNecessary, storeSession, tryRetrieveSession) @@ -457,13 +458,26 @@ withSession sessionId = do case state of Just state' -> pure state'.code Nothing -> do - gist <- H.liftEffect $ fromMaybe Config.mainGist <$> getQueryStringMaybe "gist" - loadFromGist gist + mbGitHub <- H.liftEffect $ getQueryStringMaybe "github" + mbGist <- H.liftEffect $ getQueryStringMaybe "gist" + + let + action = oneOf + [ map loadFromGitHub mbGitHub + , map loadFromGist mbGist + ] + + fromMaybe (loadFromGitHub Config.mainGitHubExample) action where - loadFromGist id = do - runExceptT (getGistById id >>= \gi -> tryLoadFileFromGist gi "Main.purs") >>= case _ of - Left err -> do - H.liftEffect $ window >>= alert err - pure "" - Right code -> - pure code + handleResult = case _ of + Left err -> do + H.liftEffect $ window >>= alert err + pure "" + Right code -> + pure code + + loadFromGist id = + runExceptT (getGistById id >>= \gi -> tryLoadFileFromGist gi "Main.purs") >>= handleResult + + loadFromGitHub id = + runExceptT (getRawGitHubFile id) >>= handleResult diff --git a/client/src/Try/GitHub.purs b/client/src/Try/GitHub.purs new file mode 100644 index 00000000..d1ccb63e --- /dev/null +++ b/client/src/Try/GitHub.purs @@ -0,0 +1,20 @@ +module Try.GitHub where + +import Prelude + +import Affjax (printError) +import Affjax as AX +import Affjax.ResponseFormat as AXRF +import Affjax.StatusCode (StatusCode(..)) +import Control.Monad.Except (ExceptT(..)) +import Data.Either (Either(..)) +import Effect.Aff (Aff) + +getRawGitHubFile :: String -> ExceptT String Aff String +getRawGitHubFile id = ExceptT $ AX.get AXRF.string ("https://raw.githubusercontent.com/" <> id) >>= case _ of + Left e -> + pure $ Left $ "Unable to load file from GitHub: \n" <> printError e + Right { status } | status >= StatusCode 400 -> + pure $ Left $ "Received error status code: " <> show status + Right { body } -> + pure $ Right body From 08e315a41641b86cf8686277888896d553b87552 Mon Sep 17 00:00:00 2001 From: Thomas Honeyman Date: Tue, 25 May 2021 10:54:13 -0700 Subject: [PATCH 02/12] Use SourceFile instead of multiple ids --- README.md | 7 ++++-- client/spago.dhall | 2 +- client/src/Try/Container.purs | 47 +++++++++++++++++++++-------------- 3 files changed, 34 insertions(+), 22 deletions(-) diff --git a/README.md b/README.md index b9244ea3..95228da0 100644 --- a/README.md +++ b/README.md @@ -12,7 +12,7 @@ - Run and print output or show resulting JavaScript - Multiple view modes: code, output or both - Persistent session -- Load PureScript code from Github Gists +- Load PureScript code from GitHub Gists or repository files ### Which Libraries are Available? @@ -45,8 +45,11 @@ Before deploying an updated package set, someone (your reviewer) should check th Most of these features can be controlled not only from the toolbar, but also using the [query parameters](https://en.wikipedia.org/wiki/Query_string): +- **Load From GitHub Repo**: Load PureScript code from a GitHub repository using the `github` parameter + - Example: `github=purescript/trypurescript/master/client/examples/Main.purs` will load the code from this file. Note: the file should be a single PureScript module with the module name `Main`. + - **Load From Gist**: Load PureScript code from Gist id using the `gist` parameter - - Example: `gist=37c3c97f47a43f20c548` will load the code from this Gist if the file was named `Main.purs` + - Example: `gist=37c3c97f47a43f20c548` will load the code from this Gist if the file was named `Main.purs`. - **View Mode**: Control the view mode using the `view` parameter - Options are: `code`, `output`, `both` (default) diff --git a/client/spago.dhall b/client/spago.dhall index 9d1c9531..d8c65090 100644 --- a/client/spago.dhall +++ b/client/spago.dhall @@ -41,5 +41,5 @@ , "web-html" ] , packages = ./packages.dhall -, sources = [ "src/**/*.purs", "test/**/*.purs", "../staging/src/**/*.purs" ] +, sources = [ "src/**/*.purs", "test/**/*.purs" ] } diff --git a/client/src/Try/Container.purs b/client/src/Try/Container.purs index 35c447b6..bb343f4e 100644 --- a/client/src/Try/Container.purs +++ b/client/src/Try/Container.purs @@ -37,6 +37,8 @@ import Web.HTML.Window (alert) type Slots = ( editor :: Editor.Slot Unit ) +data SourceFile = GitHub String | Gist String + type Settings = { autoCompile :: Boolean , showJs :: Boolean @@ -52,7 +54,7 @@ defaultSettings = type State = { settings :: Settings - , gistId :: Maybe String + , sourceFile :: Maybe SourceFile , compiled :: Maybe (Either String CompileResult) } @@ -99,7 +101,7 @@ component = H.mkComponent initialState :: i -> State initialState _ = { settings: defaultSettings - , gistId: Nothing + , sourceFile: Nothing , compiled: Nothing } @@ -107,7 +109,7 @@ component = H.mkComponent handleAction = case _ of Initialize -> do sessionId <- H.liftEffect $ createSessionIdIfNecessary - code <- H.liftAff $ withSession sessionId + { code, githubId, gistId } <- H.liftAff $ withSession sessionId -- Load parameters mbViewModeParam <- H.liftEffect $ getQueryStringMaybe "view" @@ -119,11 +121,9 @@ component = H.mkComponent mbAutoCompile <- H.liftEffect $ getQueryStringMaybe "compile" let autoCompile = mbAutoCompile /= Just "false" - mbGistId <- H.liftEffect $ getQueryStringMaybe "gist" - H.modify_ _ { settings = { viewMode, showJs, autoCompile } - , gistId = mbGistId + , sourceFile = oneOf [ map GitHub githubId, map Gist gistId ] } -- Set the editor contents. This will trigger a change event, causing a @@ -261,16 +261,26 @@ component = H.mkComponent , label: "Output" , onClick: UpdateSettings (_ { viewMode = Output }) } - , maybeElem state.gistId \gistId -> + , maybeElem state.sourceFile \source -> HH.li [ HP.class_ $ HH.ClassName "view_gist_li" ] - [ renderGistLink gistId ] + [ case source of + GitHub githubId -> + renderGistLink githubId + Gist gistId -> + renderGistLink gistId + ] ] ] - , maybeElem state.gistId \gistId -> + , maybeElem state.sourceFile \source -> HH.li [ HP.class_ $ HH.ClassName "menu-item view_gist_li mobile-only" ] - [ renderGistLink gistId ] + [ case source of + GitHub githubId -> + renderGistLink githubId + Gist gistId -> + renderGistLink gistId + ] , HH.li [ HP.class_ $ HH.ClassName "menu-item no-mobile" ] [ HH.label @@ -452,22 +462,21 @@ toAnnotation markerType { position, message } = , text: message } -withSession :: String -> Aff String +withSession :: String -> Aff { githubId :: Maybe String, gistId :: Maybe String, code :: String } withSession sessionId = do state <- H.liftEffect $ tryRetrieveSession sessionId - case state of - Just state' -> pure state'.code + githubId <- H.liftEffect $ getQueryStringMaybe "github" + gistId <- H.liftEffect $ getQueryStringMaybe "gist" + code <- case state of + Just { code } -> pure code Nothing -> do - mbGitHub <- H.liftEffect $ getQueryStringMaybe "github" - mbGist <- H.liftEffect $ getQueryStringMaybe "gist" - let action = oneOf - [ map loadFromGitHub mbGitHub - , map loadFromGist mbGist + [ map loadFromGitHub githubId + , map loadFromGist gistId ] - fromMaybe (loadFromGitHub Config.mainGitHubExample) action + pure { githubId, gistId, code } where handleResult = case _ of Left err -> do From 784262c61988463828fdd73706615876e64747f5 Mon Sep 17 00:00:00 2001 From: Thomas Honeyman Date: Tue, 25 May 2021 11:15:19 -0700 Subject: [PATCH 03/12] Add support for GitHub links --- client/public/index.html | 6 ++++++ client/public/js/frame.js | 6 ++++++ 2 files changed, 12 insertions(+) diff --git a/client/public/index.html b/client/public/index.html index e9cfef39..04dc1e46 100644 --- a/client/public/index.html +++ b/client/public/index.html @@ -61,6 +61,12 @@ ); window.addEventListener("message", function (event) { + if ( + event.data && + event.data.githubId + ) { + window.location.search = "github=" + event.data.githubId; + } if ( event.data && event.data.gistId && diff --git a/client/public/js/frame.js b/client/public/js/frame.js index 4530ec45..d68a5d13 100644 --- a/client/public/js/frame.js +++ b/client/public/js/frame.js @@ -47,5 +47,11 @@ gistId: event.target.pathname.split("/").slice(-1)[0] }, "*"); } + if (parent && event.target.nodeName === "A" && event.target.hostname === "github.com") { + event.preventDefault(); + parent.postMessage({ + githubId: event.target.pathname.slice(1) + }, "*"); + } }, false); })(); From 1363393c4c4aefb6e074233345230fb205e38edf Mon Sep 17 00:00:00 2001 From: Thomas Honeyman Date: Tue, 25 May 2021 11:27:33 -0700 Subject: [PATCH 04/12] Tweak support for GitHub links --- client/config/dev/Try.Config.purs | 2 +- client/config/prod/Try.Config.purs | 2 +- client/public/js/frame.js | 2 +- client/src/Try/Container.purs | 31 ++++++++++++++++++++---------- client/src/Try/GitHub.purs | 7 +++++-- 5 files changed, 29 insertions(+), 15 deletions(-) diff --git a/client/config/dev/Try.Config.purs b/client/config/dev/Try.Config.purs index fcd92ee3..a32218c7 100644 --- a/client/config/dev/Try.Config.purs +++ b/client/config/dev/Try.Config.purs @@ -7,4 +7,4 @@ compileUrl :: String compileUrl = "http://localhost:8081" mainGitHubExample :: String -mainGitHubExample = "purescript/trypurescript/master/client/examples/Main.purs" +mainGitHubExample = "/purescript/trypurescript/load-from-github/client/examples/Main.purs" diff --git a/client/config/prod/Try.Config.purs b/client/config/prod/Try.Config.purs index 726346dc..0c77c661 100644 --- a/client/config/prod/Try.Config.purs +++ b/client/config/prod/Try.Config.purs @@ -7,4 +7,4 @@ compileUrl :: String compileUrl = "https://compile.purescript.org" mainGitHubExample :: String -mainGitHubExample = "purescript/trypurescript/master/client/examples/Main.purs" +mainGitHubExample = "/purescript/trypurescript/load-from-github/client/examples/Main.purs" diff --git a/client/public/js/frame.js b/client/public/js/frame.js index d68a5d13..f0d0a6ff 100644 --- a/client/public/js/frame.js +++ b/client/public/js/frame.js @@ -50,7 +50,7 @@ if (parent && event.target.nodeName === "A" && event.target.hostname === "github.com") { event.preventDefault(); parent.postMessage({ - githubId: event.target.pathname.slice(1) + githubId: event.target.pathname }, "*"); } }, false); diff --git a/client/src/Try/Container.purs b/client/src/Try/Container.purs index bb343f4e..fea662c7 100644 --- a/client/src/Try/Container.purs +++ b/client/src/Try/Container.purs @@ -109,7 +109,7 @@ component = H.mkComponent handleAction = case _ of Initialize -> do sessionId <- H.liftEffect $ createSessionIdIfNecessary - { code, githubId, gistId } <- H.liftAff $ withSession sessionId + { code, sourceFile } <- H.liftAff $ withSession sessionId -- Load parameters mbViewModeParam <- H.liftEffect $ getQueryStringMaybe "view" @@ -123,7 +123,7 @@ component = H.mkComponent H.modify_ _ { settings = { viewMode, showJs, autoCompile } - , sourceFile = oneOf [ map GitHub githubId, map Gist gistId ] + , sourceFile = sourceFile } -- Set the editor contents. This will trigger a change event, causing a @@ -263,10 +263,10 @@ component = H.mkComponent } , maybeElem state.sourceFile \source -> HH.li - [ HP.class_ $ HH.ClassName "view_gist_li" ] + [ HP.class_ $ HH.ClassName "view_sourcefile_li" ] [ case source of GitHub githubId -> - renderGistLink githubId + renderGitHubLink githubId Gist gistId -> renderGistLink gistId ] @@ -274,10 +274,10 @@ component = H.mkComponent ] , maybeElem state.sourceFile \source -> HH.li - [ HP.class_ $ HH.ClassName "menu-item view_gist_li mobile-only" ] + [ HP.class_ $ HH.ClassName "menu-item view_sourcefile_li mobile-only" ] [ case source of GitHub githubId -> - renderGistLink githubId + renderGitHubLink githubId Gist gistId -> renderGistLink gistId ] @@ -440,8 +440,7 @@ menuRadio props = renderGistLink :: forall w i. String -> HH.HTML w i renderGistLink gistId = HH.a - [ HP.class_ $ HH.ClassName "view_gist" - , HP.href $ "https://gist.github.com/" <> gistId + [ HP.href $ "https://gist.github.com/" <> gistId , HP.target "trypurs_gist" ] [ HH.label @@ -449,6 +448,17 @@ renderGistLink gistId = [ HH.text "Gist" ] ] +renderGitHubLink :: forall w i. String -> HH.HTML w i +renderGitHubLink githubId = + HH.a + [ HP.href $ "https://github.com/" <> githubId + , HP.target "trypurs_github" + ] + [ HH.label + [ HP.title "Open the original source file in a new window." ] + [ HH.text "GitHub" ] + ] + toAnnotation :: forall r . MarkerType @@ -462,7 +472,7 @@ toAnnotation markerType { position, message } = , text: message } -withSession :: String -> Aff { githubId :: Maybe String, gistId :: Maybe String, code :: String } +withSession :: String -> Aff { sourceFile :: Maybe SourceFile, code :: String } withSession sessionId = do state <- H.liftEffect $ tryRetrieveSession sessionId githubId <- H.liftEffect $ getQueryStringMaybe "github" @@ -476,7 +486,8 @@ withSession sessionId = do , map loadFromGist gistId ] fromMaybe (loadFromGitHub Config.mainGitHubExample) action - pure { githubId, gistId, code } + let sourceFile = oneOf [ map GitHub githubId, map Gist gistId ] + pure { sourceFile, code } where handleResult = case _ of Left err -> do diff --git a/client/src/Try/GitHub.purs b/client/src/Try/GitHub.purs index d1ccb63e..6a2aa07d 100644 --- a/client/src/Try/GitHub.purs +++ b/client/src/Try/GitHub.purs @@ -2,7 +2,7 @@ module Try.GitHub where import Prelude -import Affjax (printError) +import Affjax (URL, printError) import Affjax as AX import Affjax.ResponseFormat as AXRF import Affjax.StatusCode (StatusCode(..)) @@ -10,8 +10,11 @@ import Control.Monad.Except (ExceptT(..)) import Data.Either (Either(..)) import Effect.Aff (Aff) +mkGitHubUrl :: String -> URL +mkGitHubUrl id = "https://raw.githubusercontent.com/" <> id + getRawGitHubFile :: String -> ExceptT String Aff String -getRawGitHubFile id = ExceptT $ AX.get AXRF.string ("https://raw.githubusercontent.com/" <> id) >>= case _ of +getRawGitHubFile id = ExceptT $ AX.get AXRF.string (mkGitHubUrl id) >>= case _ of Left e -> pure $ Left $ "Unable to load file from GitHub: \n" <> printError e Right { status } | status >= StatusCode 400 -> From 9c7b233a71573b3ddb71d6c477ebc1bf10b9ef32 Mon Sep 17 00:00:00 2001 From: Thomas Honeyman Date: Tue, 25 May 2021 11:33:25 -0700 Subject: [PATCH 05/12] Add all example files --- client/examples/ADTs.purs | 23 +++++++++++++ client/examples/DoNotation.purs | 20 ++++++++++++ client/examples/Generic.purs | 56 ++++++++++++++++++++++++++++++++ client/examples/Loops.purs | 12 +++++++ client/examples/Operators.purs | 20 ++++++++++++ client/examples/QuickCheck.purs | 21 ++++++++++++ client/examples/Records.purs | 17 ++++++++++ client/examples/Recursion.purs | 17 ++++++++++ client/examples/TypeClasses.purs | 44 +++++++++++++++++++++++++ 9 files changed, 230 insertions(+) create mode 100644 client/examples/ADTs.purs create mode 100644 client/examples/DoNotation.purs create mode 100644 client/examples/Generic.purs create mode 100644 client/examples/Loops.purs create mode 100644 client/examples/Operators.purs create mode 100644 client/examples/QuickCheck.purs create mode 100644 client/examples/Records.purs create mode 100644 client/examples/Recursion.purs create mode 100644 client/examples/TypeClasses.purs diff --git a/client/examples/ADTs.purs b/client/examples/ADTs.purs new file mode 100644 index 00000000..5bc0dec5 --- /dev/null +++ b/client/examples/ADTs.purs @@ -0,0 +1,23 @@ +module Main where + +import Prelude + +import Effect.Console (logShow) +import Data.Map (Map, lookup, singleton) +import TryPureScript (render, withConsole) + +-- | A Name consists of a first name and a last name +data Name = Name String String + +-- | With compiler versions >= 0.8.2, we can derive +-- | instances for Eq and Ord, making names comparable. +derive instance eqName :: Eq Name +derive instance ordName :: Ord Name + +-- | The Ord instance allows us to use Names as the +-- | keys in a Map. +phoneBook :: Map Name String +phoneBook = singleton (Name "John" "Smith") "555-555-1234" + +main = render =<< withConsole do + logShow (lookup (Name "John" "Smith") phoneBook) diff --git a/client/examples/DoNotation.purs b/client/examples/DoNotation.purs new file mode 100644 index 00000000..98bc3141 --- /dev/null +++ b/client/examples/DoNotation.purs @@ -0,0 +1,20 @@ +module Main where + +import Prelude +import Control.MonadPlus (guard) +import Effect.Console (logShow) +import Data.Array ((..)) +import Data.Foldable (for_) +import TryPureScript + +-- Find Pythagorean triples using an array comprehension. +triples :: Int -> Array (Array Int) +triples n = do + z <- 1 .. n + y <- 1 .. z + x <- 1 .. y + guard $ x * x + y * y == z * z + pure [x, y, z] + +main = render =<< withConsole do + for_ (triples 20) logShow diff --git a/client/examples/Generic.purs b/client/examples/Generic.purs new file mode 100644 index 00000000..44a8e362 --- /dev/null +++ b/client/examples/Generic.purs @@ -0,0 +1,56 @@ +module Main where + +import Prelude +import Effect.Console (logShow) +import Data.Generic.Rep (class Generic) +import Data.Generic.Rep.Eq (genericEq) +import Data.Generic.Rep.Ord (genericCompare) +import Data.Generic.Rep.Show (genericShow) +import TryPureScript (render, withConsole) + +data Address = Address + { city :: String + , state :: String + } + +data Person = Person + { first :: String + , last :: String + , address :: Address + } + +-- Generic instances can be derived by the compiler, +-- using the derive keyword: +derive instance genericAddress :: Generic Address _ + +derive instance genericPerson :: Generic Person _ + +-- Now we can write instances for standard type classes +-- (Show, Eq, Ord) by using standard definitions +instance showAddress :: Show Address where + show = genericShow + +instance eqAddress :: Eq Address where + eq = genericEq + +instance ordAddress :: Ord Address where + compare = genericCompare + +instance showPerson :: Show Person where + show = genericShow + +instance eqPerson :: Eq Person where + eq = genericEq + +instance ordPerson :: Ord Person where + compare = genericCompare + +main = render =<< withConsole do + logShow $ Person + { first: "John" + , last: "Smith" + , address: Address + { city: "Faketown" + , state: "CA" + } + } diff --git a/client/examples/Loops.purs b/client/examples/Loops.purs new file mode 100644 index 00000000..fc0e1290 --- /dev/null +++ b/client/examples/Loops.purs @@ -0,0 +1,12 @@ +module Main where + +import Prelude + +import Effect.Console (log) +import Data.Array ((..)) +import Data.Foldable (for_) +import TryPureScript (render, withConsole) + +main = render =<< withConsole do + for_ (10 .. 1) \n -> log (show n <> "...") + log "Lift off!" diff --git a/client/examples/Operators.purs b/client/examples/Operators.purs new file mode 100644 index 00000000..23f56351 --- /dev/null +++ b/client/examples/Operators.purs @@ -0,0 +1,20 @@ +module Main where + +import Prelude +import Effect.Console (log) +import TryPureScript (render, withConsole) + +type FilePath = String + +subdirectory :: FilePath -> FilePath -> FilePath +subdirectory p1 p2 = p1 <> "/" <> p2 + +-- Functions can be given an infix alias +-- The generated code will still use the original function name +infixl 5 subdirectory as + +filepath :: FilePath +filepath = "usr" "local" "bin" + +main = render =<< withConsole do + log filepath diff --git a/client/examples/QuickCheck.purs b/client/examples/QuickCheck.purs new file mode 100644 index 00000000..e513109d --- /dev/null +++ b/client/examples/QuickCheck.purs @@ -0,0 +1,21 @@ +module Main where + +import Prelude +import Data.Array (sort) +import Test.QuickCheck (quickCheck, (===)) +import TryPureScript (render, withConsole, h1, h2, p, text) + +main = do + render $ h1 $ text "QuickCheck" + render $ p $ text """QuickCheck is a Haskell library which allows us to assert properties +hold for our functions. QuickCheck uses type classes to generate +random test cases to verify those properties. +purescript-quickcheck is a port of parts of the QuickCheck library to +PureScript.""" + render $ h2 $ text "Sort function is idempotent" + render =<< withConsole do + quickCheck \(xs :: Array Int) -> sort (sort xs) === sort xs + render $ h2 $ text "Every array is sorted" + render $ p $ text "This test should fail on some array which is not sorted" + render =<< withConsole do + quickCheck \(xs :: Array Int) -> sort xs === xs diff --git a/client/examples/Records.purs b/client/examples/Records.purs new file mode 100644 index 00000000..deba7d99 --- /dev/null +++ b/client/examples/Records.purs @@ -0,0 +1,17 @@ +module Main where + +import Prelude +import Effect.Console (log) +import TryPureScript (render, withConsole) + +-- We can write functions which require certain record labels... +showPerson o = o.lastName <> ", " <> o.firstName + +-- ... but we are free to call those functions with any +-- additional arguments, such as "age" here. +main = render =<< withConsole do + log $ showPerson + { firstName: "John" + , lastName: "Smith" + , age: 30 + } diff --git a/client/examples/Recursion.purs b/client/examples/Recursion.purs new file mode 100644 index 00000000..fd213181 --- /dev/null +++ b/client/examples/Recursion.purs @@ -0,0 +1,17 @@ +module Main where + +import Prelude +import Effect.Console (logShow) +import TryPureScript (render, withConsole) + +isOdd :: Int -> Boolean +isOdd 0 = false +isOdd n = isEven (n - 1) + +isEven :: Int -> Boolean +isEven 0 = true +isEven n = isOdd (n - 1) + +main = render =<< withConsole do + logShow $ isEven 1000 + logShow $ isEven 1001 diff --git a/client/examples/TypeClasses.purs b/client/examples/TypeClasses.purs new file mode 100644 index 00000000..5853abf6 --- /dev/null +++ b/client/examples/TypeClasses.purs @@ -0,0 +1,44 @@ +module Main where + +import Prelude +import Effect.Console (log) +import TryPureScript (render, withConsole) + +-- A type class for types which can be used with +-- string interpolation. +class Interpolate a where + interpolate :: a -> String + +instance interpolateString :: Interpolate String where + interpolate = identity + +instance interpolateInt :: Interpolate Int where + interpolate = show + +-- A type class for printf functions +-- (each list of argument types will define a type class instance) +class Printf r where + printfWith :: String -> r + +-- An instance for no function arguments +-- (just return the accumulated string) +instance printfString :: Printf String where + printfWith = identity + +-- An instance for adding another argument whose +-- type is an instance of Interpolate +instance printfShow :: (Interpolate a, Printf r) => Printf (a -> r) where + printfWith s a = printfWith (s <> interpolate a) + +-- Our generic printf function +printf :: forall r. (Printf r) => r +printf = printfWith "" + +-- Now we can create custom formatters using different argument +-- types +debug :: String -> Int -> String -> String +debug uri status msg = printf "[" uri "] " status ": " msg + +main = render =<< withConsole do + log $ debug "http://www.purescript.org" 200 "OK" + log $ debug "http://bad.purescript.org" 404 "Not found" From a543a1b57b7b0b9dcf84678899b0d32d24b87df6 Mon Sep 17 00:00:00 2001 From: Thomas Honeyman Date: Tue, 25 May 2021 11:36:22 -0700 Subject: [PATCH 06/12] Update package set --- staging/packages.dhall | 2 +- staging/spago.dhall | 40 ++++++++++++++++++++++++++++++++++++++++ 2 files changed, 41 insertions(+), 1 deletion(-) diff --git a/staging/packages.dhall b/staging/packages.dhall index 5a72cb55..ef7a4ef2 100644 --- a/staging/packages.dhall +++ b/staging/packages.dhall @@ -1,5 +1,5 @@ let upstream = - https://github.com/purescript/package-sets/releases/download/psc-0.14.0-20210324/packages.dhall sha256:b4564d575da6aed1c042ca7936da97c8b7a29473b63f4515f09bb95fae8dddab + https://github.com/purescript/package-sets/releases/download/psc-0.14.1-20210516/packages.dhall sha256:f5e978371d4cdc4b916add9011021509c8d869f4c3f6d0d2694c0e03a85046c8 let overrides = {=} diff --git a/staging/spago.dhall b/staging/spago.dhall index c5757747..1996ca44 100644 --- a/staging/spago.dhall +++ b/staging/spago.dhall @@ -40,6 +40,7 @@ , "bucketchain-history-api-fallback" , "bucketchain-logger" , "bucketchain-secure" + , "bucketchain-simple-api" , "bucketchain-sslify" , "bucketchain-static" , "bytestrings" @@ -47,6 +48,9 @@ , "canvas" , "cartesian" , "catenable-lists" + , "channel" + , "channel-stream" + , "checked-exceptions" , "cheerio" , "cirru-parser" , "clipboardy" @@ -68,8 +72,10 @@ , "debug" , "decimals" , "distributive" + , "dodo-printer" , "dom-filereader" , "dom-indexed" + , "dotenv" , "downloadjs" , "drawing" , "dynamic-buffer" @@ -86,6 +92,7 @@ , "exists" , "exitcodes" , "expect-inferred" + , "express" , "ffi-foreign" , "filterable" , "fixed-points" @@ -103,28 +110,39 @@ , "freet" , "functions" , "functors" + , "fuzzy" , "gen" , "geometry-plane" , "github-actions-toolkit" , "gl-matrix" , "gomtang-basic" , "grain" + , "grain-router" , "grain-virtualized" + , "graphqlclient" , "graphs" , "group" , "halogen" , "halogen-bootstrap4" + , "halogen-css" + , "halogen-formless" , "halogen-hooks" , "halogen-hooks-extra" + , "halogen-select" + , "halogen-store" + , "halogen-storybook" , "halogen-subscriptions" , "halogen-svg-elems" , "halogen-vdom" , "heterogeneous" + , "heterogeneous-extrablatt" + , "homogeneous" , "http-methods" , "httpure" , "httpure-contrib-biscotti" , "httpure-middleware" , "identity" + , "identy" , "indexed-monad" , "inflection" , "integers" @@ -163,6 +181,7 @@ , "monoidal" , "morello" , "motsunabe" + , "mysql" , "naturals" , "nested-functor" , "newtype" @@ -180,11 +199,18 @@ , "node-sqlite3" , "node-streams" , "node-url" + , "nodemailer" , "nonempty" , "now" , "nullable" , "numbers" + , "open-folds" + , "open-memoize" + , "open-mkdirp-aff" + , "open-pairing" , "options" + , "options-extra" + , "optparse" , "ordered-collections" , "ordered-set" , "orders" @@ -209,9 +235,11 @@ , "prelude" , "prettier" , "prettier-printer" + , "pretty-logs" , "profunctor" , "profunctor-lenses" , "promises" + , "ps-cst" , "psa-utils" , "psc-ide" , "psci-support" @@ -223,6 +251,7 @@ , "quotient" , "random" , "rationals" + , "rave" , "react" , "react-basic" , "react-basic-classic" @@ -237,6 +266,8 @@ , "react-testing-library" , "read" , "record" + , "record-extra" + , "record-extra-srghma" , "redux-devtools" , "refined" , "refs" @@ -254,10 +285,14 @@ , "scrypt" , "selection-foldable" , "semirings" + , "server-sent-events" , "setimmediate" , "signal" + , "simple-ajax" , "simple-emitter" + , "simple-i18n" , "simple-json" + , "simple-jwt" , "simple-ulid" , "sized-matrices" , "sized-vectors" @@ -294,12 +329,14 @@ , "tuples" , "turf" , "type-equality" + , "typedenv" , "typelevel" , "typelevel-lists" , "typelevel-peano" , "typelevel-prelude" , "undefinable" , "undefined" + , "undefined-is-not-a-problem" , "undefined-or" , "unfoldable" , "unicode" @@ -309,12 +346,14 @@ , "unsafe-reference" , "untagged-union" , "uri" + , "url-regex-safe" , "uuid" , "validation" , "variant" , "vectorfield" , "veither" , "versions" + , "vexceptt" , "web-clipboard" , "web-cssom" , "web-dom" @@ -326,6 +365,7 @@ , "web-file" , "web-html" , "web-promise" + , "web-resize-observer" , "web-socket" , "web-storage" , "web-streams" From a70440421974ac1b28402d2a8d53c13576b14d02 Mon Sep 17 00:00:00 2001 From: Thomas Honeyman Date: Tue, 25 May 2021 11:41:39 -0700 Subject: [PATCH 07/12] Update main example with new links --- client/examples/Main.purs | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/client/examples/Main.purs b/client/examples/Main.purs index 9723626e..3d859f23 100644 --- a/client/examples/Main.purs +++ b/client/examples/Main.purs @@ -14,7 +14,7 @@ main = , h2 (text "Examples") , list (map fromExample examples) , h2 (text "Share Your Code") - , p (text "Code can be loaded from a GitHub Gist. To share code, simply include the Gist ID in the URL as follows:") + , p (text "Code can be loaded from a GitHub Gist . To share code, simply include the Gist ID in the URL as follows:") , indent (p (code (text " try.purescript.org?gist=gist-id"))) , p (fold [ text "The Gist should contain a file named " @@ -23,35 +23,35 @@ main = ]) ] where - fromExample { title, gist } = - link ("https://gist.github.com/" <> gist) (text title) + fromExample { title, source } = + link ("https://github.com/purescript/trypurescript/load-from-github/client/examples/" <> source) (text title) examples = [ { title: "Algebraic Data Types" - , gist: "387999a4467a39744ece236e69a442ec" + , source: "ADTs.purs" } , { title: "Loops" - , gist: "429eab1e957e807f9feeddbf4f573dd0" + , source: "Loops.purs" } , { title: "Operators" - , gist: "8395d2b421a5ca6d1056e301a6e12599" + , source: "Operators.purs" } , { title: "Records" - , gist: "170c3ca22f0141ed06a120a12b8243af" + , source: "Records.purs" } , { title: "Recursion" - , gist: "659ae8a085f1cf6e52fed2c35ad93643" + , source: "Recursion.purs" } , { title: "Do Notation" - , gist: "525cb36c147d3497f652028db1214ec8" + , source: "DoNotation.purs" } , { title: "Type Classes" - , gist: "b04463fd49cd4d7d385941b3b2fa226a" + , source: "TypeClasses.purs" } , { title: "Generic Programming" - , gist: "e3b6284959f65ac674d39aa981fcb8fb" + , source: "Generic.purs" } , { title: "QuickCheck" - , gist: "69f7f94fe4ff3bd47f4b" + , source: "QuickCheck.purs" } ] From 6d77ab74e3e4a873285f1848e778c4f02ce656e5 Mon Sep 17 00:00:00 2001 From: Thomas Honeyman Date: Tue, 25 May 2021 12:25:36 -0700 Subject: [PATCH 08/12] Use tag in config --- client/config/dev/Try.Config.purs | 7 ++++++- client/config/prod/Try.Config.purs | 7 ++++++- client/examples/Main.purs | 2 +- 3 files changed, 13 insertions(+), 3 deletions(-) diff --git a/client/config/dev/Try.Config.purs b/client/config/dev/Try.Config.purs index a32218c7..71d178c6 100644 --- a/client/config/dev/Try.Config.purs +++ b/client/config/dev/Try.Config.purs @@ -1,10 +1,15 @@ module Try.Config where +import Prelude + loaderUrl :: String loaderUrl = "js/output" compileUrl :: String compileUrl = "http://localhost:8081" +tag :: String +tag = "load-from-github" + mainGitHubExample :: String -mainGitHubExample = "/purescript/trypurescript/load-from-github/client/examples/Main.purs" +mainGitHubExample = "/purescript/trypurescript/" <> tag <> "/client/examples/Main.purs" diff --git a/client/config/prod/Try.Config.purs b/client/config/prod/Try.Config.purs index 0c77c661..3eac73fd 100644 --- a/client/config/prod/Try.Config.purs +++ b/client/config/prod/Try.Config.purs @@ -1,10 +1,15 @@ module Try.Config where +import Prelude + loaderUrl :: String loaderUrl = "https://compile.purescript.org/output" compileUrl :: String compileUrl = "https://compile.purescript.org" +tag :: String +tag = "load-from-github" + mainGitHubExample :: String -mainGitHubExample = "/purescript/trypurescript/load-from-github/client/examples/Main.purs" +mainGitHubExample = "/purescript/trypurescript/" <> tag <> "/client/examples/Main.purs" diff --git a/client/examples/Main.purs b/client/examples/Main.purs index 3d859f23..0f21194c 100644 --- a/client/examples/Main.purs +++ b/client/examples/Main.purs @@ -2,8 +2,8 @@ module Main where import Prelude -import Effect (Effect) import Data.Foldable (fold) +import Effect (Effect) import TryPureScript (h1, h2, p, text, list, indent, link, render, code) main :: Effect Unit From 4b446f24053145c862be1b89ea7e6f726077ea81 Mon Sep 17 00:00:00 2001 From: Thomas Honeyman Date: Tue, 25 May 2021 13:12:44 -0700 Subject: [PATCH 09/12] Fix generics example --- client/examples/Generic.purs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/client/examples/Generic.purs b/client/examples/Generic.purs index 44a8e362..1fea8470 100644 --- a/client/examples/Generic.purs +++ b/client/examples/Generic.purs @@ -3,9 +3,9 @@ module Main where import Prelude import Effect.Console (logShow) import Data.Generic.Rep (class Generic) -import Data.Generic.Rep.Eq (genericEq) -import Data.Generic.Rep.Ord (genericCompare) -import Data.Generic.Rep.Show (genericShow) +import Data.Eq.Generic (genericEq) +import Data.Ord.Generic (genericCompare) +import Data.Show.Generic (genericShow) import TryPureScript (render, withConsole) data Address = Address From 8b5f99a54a8da7063e492d16c9a615fc8d3d04a1 Mon Sep 17 00:00:00 2001 From: Thomas Honeyman Date: Tue, 25 May 2021 13:19:23 -0700 Subject: [PATCH 10/12] Update main example to describe GitHub loading --- README.md | 56 +++++++++++++++++++-------------------- client/examples/Main.purs | 13 +++++++-- 2 files changed, 39 insertions(+), 30 deletions(-) diff --git a/README.md b/README.md index 95228da0..6db2996f 100644 --- a/README.md +++ b/README.md @@ -14,7 +14,34 @@ - Persistent session - Load PureScript code from GitHub Gists or repository files -### Which Libraries are Available? +### Control Features via the Query String + +Most of these features can be controlled not only from the toolbar, but also using the [query parameters](https://en.wikipedia.org/wiki/Query_string): + +- **Load From GitHub Repo**: Load PureScript code from a GitHub repository using the `github` parameter + - Example: `github=/purescript/trypurescript/master/client/examples/Main.purs` will load the code from this file. Note: the file should be a single PureScript module with the module name `Main`. + +- **Load From Gist**: Load PureScript code from Gist id using the `gist` parameter + - Example: `gist=37c3c97f47a43f20c548` will load the code from this Gist if the file was named `Main.purs`. + +- **View Mode**: Control the view mode using the `view` parameter + - Options are: `code`, `output`, `both` (default) + - Example: `view=output` will only display the output + +- **Auto Compile**: Automatic compilation can be turned off using the `compile` parameter + - Options are: `true` (default), `false` + - Example: `compile=false` will turn auto compilation off + +- **JavaScript Code Generation**: Print the resulting JavaScript code in the output window instead of the output of the program using the `js` parameter + - Options are: `true`, `false` (default) + - Example: `js=true` will print JavaScript code instead of the program's output + +- **Session**: Load code from a session which is stored with [localStorage](https://developer.mozilla.org/en-US/docs/Web/API/Window/localStorage) using the `session` parameter + - Usually managed by Try PureScript + - Example: `session=9162f098-070f-4053-60ea-eba47021450d` (Note: will probably not work for you) + - When used with the `gist` or `github` query parameters the code will be loaded from the source file and not the session + +### Which Libraries Are Available? Try PureScript aims to provide a complete, recent package set from . The available libraries are those listed in `staging/spago.dhall`, at the versions in the package set mentioned in `staging/packages.dhall`. @@ -41,33 +68,6 @@ $ spago ls packages | cut -f 1 -d ' ' | xargs spago install Before deploying an updated package set, someone (your reviewer) should check that the memory required to hold the package set's externs files does not exceed that of the try.purescript.org server. -### Control Features via the Query String - -Most of these features can be controlled not only from the toolbar, but also using the [query parameters](https://en.wikipedia.org/wiki/Query_string): - -- **Load From GitHub Repo**: Load PureScript code from a GitHub repository using the `github` parameter - - Example: `github=purescript/trypurescript/master/client/examples/Main.purs` will load the code from this file. Note: the file should be a single PureScript module with the module name `Main`. - -- **Load From Gist**: Load PureScript code from Gist id using the `gist` parameter - - Example: `gist=37c3c97f47a43f20c548` will load the code from this Gist if the file was named `Main.purs`. - -- **View Mode**: Control the view mode using the `view` parameter - - Options are: `code`, `output`, `both` (default) - - Example: `view=output` will only display the output - -- **Auto Compile**: Automatic compilation can be turned off using the `compile` parameter - - Options are: `true` (default), `false` - - Example: `compile=false` will turn auto compilation off - -- **JavaScript Code Generation**: Print the resulting JavaScript code in the output window instead of the output of the program using the `js` parameter - - Options are: `true`, `false` (default) - - Example: `js=true` will print JavaScript code instead of the program's output - -- **Session**: Load code from a session which is stored with [localStorage](https://developer.mozilla.org/en-US/docs/Web/API/Window/localStorage) using the `session` parameter - - Usually managed by Try PureScript - - Example: `session=9162f098-070f-4053-60ea-eba47021450d` (Note: will probably not work for you) - - When used with the `gist` query parameter the code will be loaded from the Gist and not the session - ## Development ### 1. Client setup diff --git a/client/examples/Main.purs b/client/examples/Main.purs index 0f21194c..56f223ae 100644 --- a/client/examples/Main.purs +++ b/client/examples/Main.purs @@ -14,13 +14,22 @@ main = , h2 (text "Examples") , list (map fromExample examples) , h2 (text "Share Your Code") - , p (text "Code can be loaded from a GitHub Gist . To share code, simply include the Gist ID in the URL as follows:") + , p (text "A PureScript file can be loaded from GitHub from a gist or a repository. To share code using a gist, simply include the gist ID in the URL as follows:") , indent (p (code (text " try.purescript.org?gist=gist-id"))) , p (fold - [ text "The Gist should contain a file named " + [ text "The Gist should contain PureScript modulenamed " + , code (text "Main") + , text "in a file named " , code (text "Main.purs") , text " containing your PureScript code." ]) + , p (text "To share code from a repository, include the path to the source file the URL as follows:") + , indent (p (code (text " try.purescript.org?github=/owner/repo/Source.purs"))) + , p (fold + [ text "The file should be a PureScript module named " + , code (text "Main") + , text " containing your PureScript code." + ]) ] where fromExample { title, source } = From cd313a82cfa1876c473a786c95345a455e791b57 Mon Sep 17 00:00:00 2001 From: Thomas Honeyman Date: Tue, 25 May 2021 16:00:32 -0700 Subject: [PATCH 11/12] Address feedback --- README.md | 14 +++-- client/examples/Main.purs | 108 +++++++++++++++++++------------------- 2 files changed, 63 insertions(+), 59 deletions(-) diff --git a/README.md b/README.md index 6db2996f..03d4063b 100644 --- a/README.md +++ b/README.md @@ -18,11 +18,15 @@ Most of these features can be controlled not only from the toolbar, but also using the [query parameters](https://en.wikipedia.org/wiki/Query_string): -- **Load From GitHub Repo**: Load PureScript code from a GitHub repository using the `github` parameter - - Example: `github=/purescript/trypurescript/master/client/examples/Main.purs` will load the code from this file. Note: the file should be a single PureScript module with the module name `Main`. - -- **Load From Gist**: Load PureScript code from Gist id using the `gist` parameter - - Example: `gist=37c3c97f47a43f20c548` will load the code from this Gist if the file was named `Main.purs`. +- **Load From GitHub Repo**: Load a PureScript file from a GitHub repository using the `github` parameter + - Format: `github=////.purs` + - Example: `github=/purescript/trypurescript/master/client/examples/Main.purs`. + - Notes: the file should be a single PureScript module with the module name `Main`. + +- **Load From Gist**: Load PureScript code from a gist using the `gist` parameter + - Format: `gist=` + - Example: `gist=37c3c97f47a43f20c548` + - Notes: the file should be named `Main.purs` with the module name `Main`. - **View Mode**: Control the view mode using the `view` parameter - Options are: `code`, `output`, `both` (default) diff --git a/client/examples/Main.purs b/client/examples/Main.purs index 56f223ae..1e6b9f46 100644 --- a/client/examples/Main.purs +++ b/client/examples/Main.purs @@ -8,59 +8,59 @@ import TryPureScript (h1, h2, p, text, list, indent, link, render, code) main :: Effect Unit main = - render $ fold - [ h1 (text "Try PureScript!") - , p (text "Try out the examples below, or create your own!") - , h2 (text "Examples") - , list (map fromExample examples) - , h2 (text "Share Your Code") - , p (text "A PureScript file can be loaded from GitHub from a gist or a repository. To share code using a gist, simply include the gist ID in the URL as follows:") - , indent (p (code (text " try.purescript.org?gist=gist-id"))) - , p (fold - [ text "The Gist should contain PureScript modulenamed " - , code (text "Main") - , text "in a file named " - , code (text "Main.purs") - , text " containing your PureScript code." - ]) - , p (text "To share code from a repository, include the path to the source file the URL as follows:") - , indent (p (code (text " try.purescript.org?github=/owner/repo/Source.purs"))) - , p (fold - [ text "The file should be a PureScript module named " - , code (text "Main") - , text " containing your PureScript code." - ]) - ] + render $ fold + [ h1 (text "Try PureScript!") + , p (text "Try out the examples below, or create your own!") + , h2 (text "Examples") + , list (map fromExample examples) + , h2 (text "Share Your Code") + , p (text "A PureScript file can be loaded from GitHub from a gist or a repository. To share code using a gist, simply include the gist ID in the URL as follows:") + , indent (p (code (text " try.purescript.org?gist="))) + , p (fold + [ text "The gist should contain PureScript module named " + , code (text "Main") + , text " in a file named " + , code (text "Main.purs") + , text " containing your PureScript code." + ]) + , p (text "To share code from a repository, include the path to the source file as follows:") + , indent (p (code (text " try.purescript.org?github=////.purs"))) + , p (fold + [ text "The file should be a PureScript module named " + , code (text "Main") + , text " containing your PureScript code." + ]) + ] where - fromExample { title, source } = - link ("https://github.com/purescript/trypurescript/load-from-github/client/examples/" <> source) (text title) + fromExample { title, source } = + link ("https://github.com/purescript/trypurescript/load-from-github/client/examples/" <> source) (text title) - examples = - [ { title: "Algebraic Data Types" - , source: "ADTs.purs" - } - , { title: "Loops" - , source: "Loops.purs" - } - , { title: "Operators" - , source: "Operators.purs" - } - , { title: "Records" - , source: "Records.purs" - } - , { title: "Recursion" - , source: "Recursion.purs" - } - , { title: "Do Notation" - , source: "DoNotation.purs" - } - , { title: "Type Classes" - , source: "TypeClasses.purs" - } - , { title: "Generic Programming" - , source: "Generic.purs" - } - , { title: "QuickCheck" - , source: "QuickCheck.purs" - } - ] + examples = + [ { title: "Algebraic Data Types" + , source: "ADTs.purs" + } + , { title: "Loops" + , source: "Loops.purs" + } + , { title: "Operators" + , source: "Operators.purs" + } + , { title: "Records" + , source: "Records.purs" + } + , { title: "Recursion" + , source: "Recursion.purs" + } + , { title: "Do Notation" + , source: "DoNotation.purs" + } + , { title: "Type Classes" + , source: "TypeClasses.purs" + } + , { title: "Generic Programming" + , source: "Generic.purs" + } + , { title: "QuickCheck" + , source: "QuickCheck.purs" + } + ] From 146a6c5571ee8fd65241537460f8a3712d4a4097 Mon Sep 17 00:00:00 2001 From: Thomas Honeyman Date: Tue, 25 May 2021 16:08:34 -0700 Subject: [PATCH 12/12] Update readme instructions for tags --- README.md | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/README.md b/README.md index 03d4063b..16b1194d 100644 --- a/README.md +++ b/README.md @@ -105,6 +105,16 @@ stack exec trypurescript 8081 $(spago sources) # then: Setting phasers to stun... (port 8081) (ctrl-c to quit) ``` +### 3. Choosing a Tag + +The built-in examples for Try PureScript are loaded from this GitHub repository. To change the tag that the examples are loaded from, you'll need to touch three files: + +* `client/config/dev/Try.Config.purs` +* `client/config/prod/Try.Config.purs` +* `client/examples/Main.purs`, in the `fromExample` function. + +If you are preparing a release or if you need to adjust examples in development, you should change the tag in these three places (and ensure you're using the same tag in each place!). + ## Server API The server is a very basic web service which wraps the PureScript compiler, allowing clients to send PureScript code to be compiled and receiving either compiled JS or error messages in response.