aboutsummaryrefslogtreecommitdiff
path: root/frontend/src
diff options
context:
space:
mode:
authorChristine Dodrill <me@christine.website>2017-05-17 21:30:25 -0700
committerChristine Dodrill <me@christine.website>2017-05-17 21:30:25 -0700
commit30aa5d8c2ddb49ec56596edad23b5c1043737366 (patch)
treec9ec557f20482ab44a6d9fb0f997b4f1561b3503 /frontend/src
parent372573572913bebe24312b72f2c62d74bb8aba54 (diff)
downloadxesite-30aa5d8c2ddb49ec56596edad23b5c1043737366.tar.xz
xesite-30aa5d8c2ddb49ec56596edad23b5c1043737366.zip
remove code
Diffstat (limited to 'frontend/src')
-rw-r--r--frontend/src/BlogEntry.purs72
-rw-r--r--frontend/src/BlogIndex.purs86
-rw-r--r--frontend/src/Counter.purs40
-rw-r--r--frontend/src/Layout.purs188
-rw-r--r--frontend/src/Main.purs53
-rw-r--r--frontend/src/NotFound.purs8
-rw-r--r--frontend/src/Pux/DocumentTitle.js3
-rw-r--r--frontend/src/Pux/DocumentTitle.purs7
-rw-r--r--frontend/src/Resume.purs66
-rw-r--r--frontend/src/Routes.purs31
-rw-r--r--frontend/src/Utils.js16
-rw-r--r--frontend/src/Utils.purs3
12 files changed, 0 insertions, 573 deletions
diff --git a/frontend/src/BlogEntry.purs b/frontend/src/BlogEntry.purs
deleted file mode 100644
index 0a46976..0000000
--- a/frontend/src/BlogEntry.purs
+++ /dev/null
@@ -1,72 +0,0 @@
-module App.BlogEntry where
-
-import App.Utils (mdify)
-import Control.Monad.Aff (attempt)
-import DOM (DOM)
-import Data.Argonaut (class DecodeJson, decodeJson, (.?))
-import Data.Either (Either(..), either)
-import Data.Maybe (Maybe(..))
-import Network.HTTP.Affjax (AJAX, get)
-import Prelude (bind, pure, show, ($), (<>), (<<<))
-import Pux (noEffects, EffModel)
-import Pux.DocumentTitle (documentTitle)
-import Pux.Html (Html, div, h1, p, text)
-import Pux.Html.Attributes (dangerouslySetInnerHTML, className, id_, title)
-
-data Action = RequestPost
- | ReceivePost (Either String Post)
-
-type State =
- { status :: String
- , id :: Maybe Int
- , post :: Post
- , name :: String }
-
-data Post = Post
- { title :: String
- , body :: String
- , date :: String }
-
-instance decodeJsonPost :: DecodeJson Post where
- decodeJson json = do
- obj <- decodeJson json
- title <- obj .? "title"
- body <- obj .? "body"
- date <- obj .? "date"
- pure $ Post { title: title, body: body, date: date }
-
-init :: State
-init =
- { status: "Loading..."
- , post: Post
- { title: ""
- , body: ""
- , date: "" }
- , name: ""
- , id: Nothing }
-
-update :: Action -> State -> EffModel State Action (ajax :: AJAX, dom :: DOM)
-update (ReceivePost (Left err)) state =
- noEffects $ state { id = Nothing, status = err }
-update (ReceivePost (Right post)) state = noEffects $ state { status = "", id = Just 1, post = post }
-update RequestPost state =
- { state: state
- , effects: [ do
- res <- attempt $ get ("/api/blog/post?name=" <> state.name)
- let decode r = decodeJson r.response :: Either String Post
- let post = either (Left <<< show) decode res
- pure $ ReceivePost post
- ]
- }
-
-view :: State -> Html Action
-view { id: id, status: status, post: (Post post) } =
- case id of
- Nothing -> div [] []
- (Just _) ->
- div [ className "row" ]
- [ h1 [] [ text status ]
- , documentTitle [ title $ post.title <> " - Christine Dodrill" ] []
- , div [ className "col s8 offset-s2" ]
- [ p [ id_ "blogpost", dangerouslySetInnerHTML $ mdify post.body ] [] ]
- ]
diff --git a/frontend/src/BlogIndex.purs b/frontend/src/BlogIndex.purs
deleted file mode 100644
index 1b41dbf..0000000
--- a/frontend/src/BlogIndex.purs
+++ /dev/null
@@ -1,86 +0,0 @@
-module App.BlogIndex where
-
-import Control.Monad.Aff (attempt)
-import DOM (DOM)
-import Data.Argonaut (class DecodeJson, decodeJson, (.?))
-import Data.Either (Either(Left, Right), either)
-import Network.HTTP.Affjax (AJAX, get)
-import Prelude (($), bind, map, const, show, (<>), pure, (<<<))
-import Pux (EffModel, noEffects)
-import Pux.DocumentTitle (documentTitle)
-import Pux.Html (Html, br, div, h1, ol, li, button, text, span, p)
-import Pux.Html.Attributes (className, id_, key, title)
-import Pux.Html.Events (onClick)
-import Pux.Router (link)
-
-data Action = RequestPosts
- | ReceivePosts (Either String Posts)
-
-type State =
- { posts :: Posts
- , status :: String }
-
-data Post = Post
- { title :: String
- , link :: String
- , summary :: String
- , date :: String }
-
-type Posts = Array Post
-
-instance decodeJsonPost :: DecodeJson Post where
- decodeJson json = do
- obj <- decodeJson json
- title <- obj .? "title"
- link <- obj .? "link"
- summ <- obj .? "summary"
- date <- obj .? "date"
- pure $ Post { title: title, link: link, summary: summ, date: date }
-
-init :: State
-init =
- { posts: []
- , status: "" }
-
-update :: Action -> State -> EffModel State Action (ajax :: AJAX, dom :: DOM)
-update (ReceivePosts (Left err)) state =
- noEffects $ state { status = ("error: " <> err) }
-update (ReceivePosts (Right posts)) state =
- noEffects $ state { posts = posts, status = "" }
-update RequestPosts state =
- { state: state { status = "Loading..." }
- , effects: [ do
- res <- attempt $ get "/api/blog/posts"
- let decode r = decodeJson r.response :: Either String Posts
- let posts = either (Left <<< show) decode res
- pure $ ReceivePosts posts
- ]
- }
-
-post :: Post -> Html Action
-post (Post state) =
- div
- [ className "col s6" ]
- [ div
- [ className "card pink lighten-5" ]
- [ div
- [ className "card-content black-text" ]
- [ span [ className "card-title" ] [ text state.title ]
- , br [] []
- , p [] [ text ("Posted on: " <> state.date) ]
- , span [] [ text state.summary ]
- ]
- , div
- [ className "card-action pink lighten-5" ]
- [ link state.link [] [ text "Read More" ] ]
- ]
- ]
-
-view :: State -> Html Action
-view state =
- div
- []
- [ h1 [] [ text "Posts" ]
- , documentTitle [ title "Posts - Christine Dodrill" ] []
- , div [ className "row" ] $ map post state.posts
- , p [] [ text state.status ] ]
diff --git a/frontend/src/Counter.purs b/frontend/src/Counter.purs
deleted file mode 100644
index d56afbe..0000000
--- a/frontend/src/Counter.purs
+++ /dev/null
@@ -1,40 +0,0 @@
-module App.Counter where
-
-import Prelude ((+), (-), const, show)
-import Pux.Html (Html, a, br, div, span, text)
-import Pux.Html.Attributes (className, href)
-import Pux.Html.Events (onClick)
-
-data Action = Increment | Decrement
-
-type State = Int
-
-init :: State
-init = 0
-
-update :: Action -> State -> State
-update Increment state = state + 1
-update Decrement state = state - 1
-
-view :: State -> Html Action
-view state =
- div
- [ className "row" ]
- [ div
- [ className "col s4 offset-s4" ]
- [ div
- [ className "card blue-grey darken-1" ]
- [ div
- [ className "card-content white-text" ]
- [ span [ className "card-title" ] [ text "Counter" ]
- , br [] []
- , span [] [ text (show state) ]
- ]
- , div
- [ className "card-action" ]
- [ a [ onClick (const Increment), href "#" ] [ text "Increment" ]
- , a [ onClick (const Decrement), href "#" ] [ text "Decrement" ]
- ]
- ]
- ]
- ]
diff --git a/frontend/src/Layout.purs b/frontend/src/Layout.purs
deleted file mode 100644
index 193419e..0000000
--- a/frontend/src/Layout.purs
+++ /dev/null
@@ -1,188 +0,0 @@
-module App.Layout where
-
-import App.BlogEntry as BlogEntry
-import App.BlogIndex as BlogIndex
-import App.Counter as Counter
-import App.Resume as Resume
-import Pux.Html as H
-import App.Routes (Route(..))
-import Control.Monad.RWS (state)
-import DOM (DOM)
-import Network.HTTP.Affjax (AJAX)
-import Prelude (($), (#), map, pure)
-import Pux (EffModel, noEffects, mapEffects, mapState)
-import Pux.DocumentTitle (documentTitle)
-import Pux.Html (style, Html, a, code, div, h1, h2, h3, h4, li, nav, p, pre, text, ul, img, span)
-import Pux.Html (Html, a, code, div, h1, h3, h4, li, nav, p, pre, text, ul)
-import Pux.Html.Attributes (attr, target, href, classID, className, id_, role, src, rel, title)
-import Pux.Router (link)
-
-data Action
- = Child (Counter.Action)
- | BIChild (BlogIndex.Action)
- | BEChild (BlogEntry.Action)
- | REChild (Resume.Action)
- | PageView Route
-
-type State =
- { route :: Route
- , count :: Counter.State
- , bistate :: BlogIndex.State
- , bestate :: BlogEntry.State
- , restate :: Resume.State }
-
-init :: State
-init =
- { route: NotFound
- , count: Counter.init
- , bistate: BlogIndex.init
- , bestate: BlogEntry.init
- , restate: Resume.init }
-
-update :: Action -> State -> EffModel State Action (ajax :: AJAX, dom :: DOM)
-update (PageView route) state = routeEffects route $ state { route = route }
-update (BIChild action) state = BlogIndex.update action state.bistate
- # mapState (state { bistate = _ })
- # mapEffects BIChild
-update (BEChild action) state = BlogEntry.update action state.bestate
- # mapState (state { bestate = _ })
- # mapEffects BEChild
-update (REChild action) state = Resume.update action state.restate
- # mapState ( state { restate = _ })
- # mapEffects REChild
-update (Child action) state = noEffects $ state { count = Counter.update action state.count }
-update _ state = noEffects $ state
-
-routeEffects :: Route -> State -> EffModel State Action (dom :: DOM, ajax :: AJAX)
-routeEffects (BlogIndex) state = { state: state
- , effects: [ pure BlogIndex.RequestPosts ] } # mapEffects BIChild
-routeEffects (Resume) state = { state: state
- , effects: [ pure Resume.RequestResume ] } # mapEffects REChild
-routeEffects (BlogPost page') state = { state: state { bestate = BlogEntry.init { name = page' } }
- , effects: [ pure BlogEntry.RequestPost ] } # mapEffects BEChild
-routeEffects _ state = noEffects $ state
-
-view :: State -> Html Action
-view state =
- div
- []
- [ navbar state
- , div
- [ className "container" ]
- [ page state.route state ]
- ]
-
-navbar :: State -> Html Action
-navbar state =
- nav
- [ className "pink lighten-1", role "navigation" ]
- [ div
- [ className "nav-wrapper container" ]
- [ link "/" [ className "brand-logo", id_ "logo-container" ] [ text "Christine Dodrill" ]
- , H.link [ rel "stylesheet", href "/static/css/about/main.css" ] []
- , ul
- [ className "right hide-on-med-and-down" ]
- [ li [] [ link "/blog" [] [ text "Blog" ] ]
- -- , li [] [ link "/projects" [] [ text "Projects" ] ]
- , li [] [ link "/resume" [] [ text "Resume" ] ]
- , li [] [ link "/contact" [] [ text "Contact" ] ]
- ]
- ]
- ]
-
-contact :: Html Action
-contact =
- div
- [ className "row" ]
- [ documentTitle [ title "Contact - Christine Dodrill" ] []
- , div
- [ className "col s6" ]
- [ h3 [] [ text "Email" ]
- , div [ className "email" ] [ text "me@christine.website" ]
- , p []
- [ text "My GPG fingerprint is "
- , code [] [ text "799F 9134 8118 1111" ]
- , text ". If you get an email that appears to be from me and the signature does not match that fingerprint, it is not from me. You may download a copy of my public key "
- , a [ href "/static/gpg.pub" ] [ text "here" ]
- , text "."
- ]
- , h3 [] [ text "Social Media" ]
- , ul
- [ className "browser-default" ]
- [ li [] [ a [ href "https://github.com/Xe" ] [ text "Github" ] ]
- , li [] [ a [ href "https://twitter.com/theprincessxena"] [ text "Twitter" ] ]
- , li [] [ a [ href "https://keybase.io/xena" ] [ text "Keybase" ] ]
- , li [] [ a [ href "https://www.coinbase.com/christinedodrill" ] [ text "Coinbase" ] ]
- , li [] [ a [ href "https://www.facebook.com/chrissycade1337" ] [ text "Facebook" ] ]
- ]
- ]
- , div
- [ className "col s6" ]
- [ h3 [] [ text "Other Information" ]
- , p []
- [ text "To send me donations, my bitcoin address is "
- , code [] [ text "1Gi2ZF2C9CU9QooH8bQMB2GJ2iL6shVnVe" ]
- , text "."
- ]
- , div []
- [ h4 [] [ text "IRC" ]
- , p [] [ text "I am on many IRC networks. On Freenode I am using the nick Xe but elsewhere I will use the nick Xena or Cadey." ]
- ]
- , div []
- [ h4 [] [ text "Telegram" ]
- , a [ href "https://telegram.me/miamorecadenza" ] [ text "@miamorecadenza" ]
- ]
- , div []
- [ h4 [] [ text "Discord" ]
- , pre [] [ text "Cadey~#1932" ]
- ]
- ]
- ]
-
-index :: Html Action
-index =
- div
- [ className "row panel" ]
- [ documentTitle [ title "Christine Dodrill" ] []
- , div [] [ div
- [ className "col m4 bg_blur valign-wrapper center-align" ]
- [ div
- [ className "valign center-align fb_wrap" ]
- [ link "/contact"
- [ className "btn follow_btn" ]
- [ text "Contact Me" ]
- ]
- ]
- ]
- , div
- [ className "col m8" ]
- [ div
- [ className "header" ]
- [ h1 [] [ text "Christine Dodrill" ]
- , h4 [] [ text "Rockstar Hacker, Freelance Programmer, Gopher, Cloud Architect" ]
- , span [] [ text "I am a GitHub power user. I am constantly learning new languages and tools. I strongly believe in knowing many languages and ways to do things so I can pick the right tool for the job." ]
- , h2 [] [ text "Skills" ]
- , ul
- [ className "browser-default" ]
- [ li [] [ text "Go, Moonscript, Lua, Python, C, Nim, Haskell" ]
- , li [] [ text "Docker deployments" ]
- , li [] [ text "Research, Development and Experimentation" ]
- ]
- , h2 [] [ text "Side Projects" ]
- , ul
- [ className "browser-default" ]
- [ li [] [ text "Real-time globally distributed chat server maintenance" ]
- , li [] [ text "Mashups of chat, video and music" ]
- ]
- ]
- ]
- ]
-
-page :: Route -> State -> Html Action
-page NotFound _ = h1 [] [ text "not found" ]
-page Home _ = index
-page Resume state = map REChild $ Resume.view state.restate
-page BlogIndex state = map BIChild $ BlogIndex.view state.bistate
-page (BlogPost _) state = map BEChild $ BlogEntry.view state.bestate
-page ContactPage _ = contact
-page _ _ = h1 [] [ text "not implemented yet" ]
diff --git a/frontend/src/Main.purs b/frontend/src/Main.purs
deleted file mode 100644
index 09030f3..0000000
--- a/frontend/src/Main.purs
+++ /dev/null
@@ -1,53 +0,0 @@
-module Main where
-
-import App.Layout (Action(PageView), State, view, update)
-import App.Routes (match)
-import Control.Bind ((=<<))
-import Control.Monad.Eff (Eff)
-import DOM (DOM)
-import Network.HTTP.Affjax (AJAX)
-import Prelude (bind, pure)
-import Pux (renderToDOM, renderToString, App, Config, CoreEffects, start)
-import Pux.Devtool (Action, start) as Pux.Devtool
-import Pux.Router (sampleUrl)
-import Signal ((~>))
-
-type AppEffects = (dom :: DOM, ajax :: AJAX)
-
--- | App configuration
-config :: forall eff. State -> Eff (dom :: DOM | eff) (Config State Action AppEffects)
-config state = do
- -- | Create a signal of URL changes.
- urlSignal <- sampleUrl
-
- -- | Map a signal of URL changes to PageView actions.
- let routeSignal = urlSignal ~> \r -> PageView (match r)
-
- pure
- { initialState: state
- , update: update
- , view: view
- , inputs: [routeSignal] }
-
--- | Entry point for the browser.
-main :: State -> Eff (CoreEffects AppEffects) (App State Action)
-main state = do
- app <- start =<< config state
- renderToDOM "#app" app.html
- -- | Used by hot-reloading code in support/index.js
- pure app
-
--- | Entry point for the browser with pux-devtool injected.
-debug :: State -> Eff (CoreEffects AppEffects) (App State (Pux.Devtool.Action Action))
-debug state = do
- app <- Pux.Devtool.start =<< config state
- renderToDOM "#app" app.html
- -- | Used by hot-reloading code in support/index.js
- pure app
-
--- | Entry point for server side rendering
-ssr :: State -> Eff (CoreEffects AppEffects) String
-ssr state = do
- app <- start =<< config state
- res <- renderToString app.html
- pure res
diff --git a/frontend/src/NotFound.purs b/frontend/src/NotFound.purs
deleted file mode 100644
index d22d26d..0000000
--- a/frontend/src/NotFound.purs
+++ /dev/null
@@ -1,8 +0,0 @@
-module App.NotFound where
-
-import Pux.Html (Html, (#), div, h2, text)
-
-view :: forall state action. state -> Html action
-view state =
- div # do
- h2 # text "404 Not Found"
diff --git a/frontend/src/Pux/DocumentTitle.js b/frontend/src/Pux/DocumentTitle.js
deleted file mode 100644
index 4813319..0000000
--- a/frontend/src/Pux/DocumentTitle.js
+++ /dev/null
@@ -1,3 +0,0 @@
-var Pux = require('purescript-pux');
-
-exports.documentTitle = Pux.fromReact(require('react-document-title'));
diff --git a/frontend/src/Pux/DocumentTitle.purs b/frontend/src/Pux/DocumentTitle.purs
deleted file mode 100644
index 584af35..0000000
--- a/frontend/src/Pux/DocumentTitle.purs
+++ /dev/null
@@ -1,7 +0,0 @@
-module Pux.DocumentTitle where
-
-import Pux.Html (Html, Attribute)
-
--- | Declaratively set `document.title`. See [react-document-title](https://github.com/gaearon/react-document-title)
--- | for more information.
-foreign import documentTitle :: forall a. Array (Attribute a) -> Array (Html a) -> Html a
diff --git a/frontend/src/Resume.purs b/frontend/src/Resume.purs
deleted file mode 100644
index 8a23d02..0000000
--- a/frontend/src/Resume.purs
+++ /dev/null
@@ -1,66 +0,0 @@
-module App.Resume where
-
-import App.Utils (mdify)
-import Control.Monad.Aff (attempt)
-import DOM (DOM)
-import Data.Argonaut (class DecodeJson, decodeJson, (.?))
-import Data.Either (Either(..), either)
-import Data.Maybe (Maybe(..))
-import Network.HTTP.Affjax (AJAX, get)
-import Prelude (Unit, bind, pure, show, unit, ($), (<>), (<<<))
-import Pux (noEffects, EffModel)
-import Pux.DocumentTitle (documentTitle)
-import Pux.Html (Html, a, div, h1, p, text)
-import Pux.Html.Attributes (href, dangerouslySetInnerHTML, className, id_, title)
-
-data Action = RequestResume
- | ReceiveResume (Either String Resume)
-
-type State =
- { status :: String
- , err :: String
- , resume :: Maybe Resume }
-
-data Resume = Resume
- { body :: String }
-
-instance decodeJsonResume :: DecodeJson Resume where
- decodeJson json = do
- obj <- decodeJson json
- body <- obj .? "body"
- pure $ Resume { body: body }
-
-init :: State
-init =
- { status: "Loading..."
- , err: ""
- , resume: Nothing }
-
-update :: Action -> State -> EffModel State Action (ajax :: AJAX, dom :: DOM)
-update (ReceiveResume (Left err)) state =
- noEffects $ state { resume = Nothing, status = "Error in fetching resume, please use the plain text link below.", err = err }
-update (ReceiveResume (Right body)) state =
- noEffects $ state { status = "", err = "", resume = Just body }
- where
- got' = Just unit
-update RequestResume state =
- { state: state
- , effects: [ do
- res <- attempt $ get "/api/resume"
- let decode r = decodeJson r.response :: Either String Resume
- let resume = either (Left <<< show) decode res
- pure $ ReceiveResume resume
- ]
- }
-
-view :: State -> Html Action
-view { status: status, err: err, resume: resume } =
- case resume of
- Nothing -> div [] [ text status, p [] [ text err ] ]
- (Just (Resume resume')) ->
- div [ className "row" ]
- [ documentTitle [ title "Resume - Christine Dodrill" ] []
- , div [ className "col s8 offset-s2" ]
- [ p [ className "browser-default", dangerouslySetInnerHTML $ mdify resume'.body ] []
- , a [ href "/static/resume/resume.md" ] [ text "Plain-text version of this resume here" ], text "." ]
- ]
diff --git a/frontend/src/Routes.purs b/frontend/src/Routes.purs
deleted file mode 100644
index 7076898..0000000
--- a/frontend/src/Routes.purs
+++ /dev/null
@@ -1,31 +0,0 @@
-module App.Routes where
-
-import App.BlogEntry as BlogEntry
-import App.BlogIndex as BlogIndex
-import App.Counter as Counter
-import Control.Alt ((<|>))
-import Control.Apply ((<*), (*>))
-import Data.Functor ((<$))
-import Data.Maybe (fromMaybe)
-import Prelude (($), (<$>))
-import Pux.Router (param, router, lit, str, end)
-
-data Route = Home
- | Resume
- | ContactPage
- | StaticPage String
- | BlogIndex
- | BlogPost String
- | NotFound
-
-match :: String -> Route
-match url = fromMaybe NotFound $ router url $
- Home <$ end
- <|>
- BlogIndex <$ lit "blog" <* end
- <|>
- BlogPost <$> (lit "blog" *> str) <* end
- <|>
- ContactPage <$ lit "contact" <* end
- <|>
- Resume <$ lit "resume" <* end
diff --git a/frontend/src/Utils.js b/frontend/src/Utils.js
deleted file mode 100644
index 61023c8..0000000
--- a/frontend/src/Utils.js
+++ /dev/null
@@ -1,16 +0,0 @@
-// Module App.BlogEntry
-
-showdown = require("showdown");
-
-showdown.extension('blog', function() {
- return [{
- type: 'output',
- regex: /<ul>/g,
- replace: '<ul class="browser-default">'
- }];
-});
-
-exports.mdify = function(corpus) {
- var converter = new showdown.Converter({ extensions: ['blog'] });
- return converter.makeHtml(corpus);
-};
diff --git a/frontend/src/Utils.purs b/frontend/src/Utils.purs
deleted file mode 100644
index 2d3c8a9..0000000
--- a/frontend/src/Utils.purs
+++ /dev/null
@@ -1,3 +0,0 @@
-module App.Utils where
-
-foreign import mdify :: String -> String