upload gpx file (cargo-culted, very rough)
This commit is contained in:
parent
0d4da6ec93
commit
1b8293f93e
86
app/Main.hs
86
app/Main.hs
@ -1,17 +1,25 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
{-# LANGUAGE QuasiQuotes #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
|
|
||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import Track(parseFile)
|
import Data.ByteString.Lazy as BS
|
||||||
import Data.List as List
|
import Data.List as List
|
||||||
|
import Data.Text as T
|
||||||
|
import Debug.Trace (traceShow)
|
||||||
|
import Track (parseBS, parseFile)
|
||||||
|
-- import Import
|
||||||
|
|
||||||
import Yesod.Core
|
import Yesod.Core
|
||||||
|
import Yesod.Form.Fields
|
||||||
|
import Yesod.Form.Functions
|
||||||
|
import Yesod.Form.Types
|
||||||
-- https://github.com/yesodweb/yesod-cookbook/blob/master/cookbook/Static-file-subsite-Hello-World.md
|
-- https://github.com/yesodweb/yesod-cookbook/blob/master/cookbook/Static-file-subsite-Hello-World.md
|
||||||
import Yesod.Static
|
import Yesod.Static
|
||||||
|
|
||||||
staticFiles "frontend" -- this param appears to be a pathname
|
staticFiles "frontend" -- this param appears to be a pathname
|
||||||
|
|
||||||
data Souplesse = Souplesse
|
data Souplesse = Souplesse
|
||||||
@ -20,42 +28,92 @@ data Souplesse = Souplesse
|
|||||||
|
|
||||||
-- ref https://www.yesodweb.com/book/routing-and-handlers
|
-- ref https://www.yesodweb.com/book/routing-and-handlers
|
||||||
-- for adding params (start/end) to the timeline route
|
-- for adding params (start/end) to the timeline route
|
||||||
mkYesod "Souplesse" [parseRoutes|
|
mkYesod
|
||||||
|
"Souplesse"
|
||||||
|
[parseRoutes|
|
||||||
/ CalendarR GET
|
/ CalendarR GET
|
||||||
/timeline TimelineR GET
|
/timeline TimelineR GET
|
||||||
|
/upload UploadR POST
|
||||||
/static StaticR Static getStatic
|
/static StaticR Static getStatic
|
||||||
|]
|
|]
|
||||||
|
|
||||||
instance Yesod Souplesse
|
instance Yesod Souplesse
|
||||||
|
|
||||||
getCalendarR :: Handler Html
|
getCalendarR :: Handler Html
|
||||||
getCalendarR = defaultLayout [whamlet|
|
getCalendarR = do
|
||||||
<h1>Calendar</h1>
|
(formWidget, formEnctype) <- generateFormPost uploadForm
|
||||||
|
defaultLayout
|
||||||
|
[whamlet|
|
||||||
|
<h1>Calendar
|
||||||
|
|
||||||
<p>A calendar view goes here
|
<p>A calendar view goes here
|
||||||
|
|
||||||
<a href="/timeline">timeline</a>
|
<form action="/upload" method=post enctype="multipart/form-data">
|
||||||
|
^{formWidget}
|
||||||
|
<input type="submit" name="send" value="send">
|
||||||
|
|
||||||
|
<a href="/timeline">timeline
|
||||||
© 2024 Daniel Barlow
|
© 2024 Daniel Barlow
|
||||||
|]
|
|]
|
||||||
|
|
||||||
getTimelineR :: Handler Html
|
getTimelineR :: Handler Html
|
||||||
|
|
||||||
-- what's this about? <img src=@{StaticR image_png}/>|]
|
-- what's this about? <img src=@{StaticR image_png}/>|]
|
||||||
getTimelineR = defaultLayout $ do
|
getTimelineR = defaultLayout $ do
|
||||||
setTitle "timeline"
|
setTitle "timeline"
|
||||||
addScriptRemote "/static/frontend.js"
|
addScriptRemote "/static/frontend.js"
|
||||||
toWidgetBody [julius|
|
toWidgetBody
|
||||||
|
[julius|
|
||||||
window.addEventListener("load", function(){
|
window.addEventListener("load", function(){
|
||||||
var app = Elm.Main.init({
|
var app = Elm.Main.init({
|
||||||
node: document.getElementById("elm")
|
node: document.getElementById("elm")
|
||||||
});
|
});
|
||||||
})
|
})
|
||||||
|]
|
|]
|
||||||
toWidget [hamlet|
|
toWidget
|
||||||
|
[hamlet|
|
||||||
<pre id="elm">
|
<pre id="elm">
|
||||||
<p>Copyright © 2024 Daniel Barlow
|
<p>Copyright © 2024 Daniel Barlow
|
||||||
|]
|
|]
|
||||||
|
|
||||||
|
-- data File = File
|
||||||
|
|
||||||
|
data FileForm = FileForm
|
||||||
|
{ fileInfo :: FileInfo
|
||||||
|
-- , fileDescription :: Text
|
||||||
|
}
|
||||||
|
|
||||||
|
type Form x = Html -> MForm (HandlerFor Souplesse) (FormResult x, Widget)
|
||||||
|
|
||||||
|
uploadForm :: Form FileForm
|
||||||
|
uploadForm =
|
||||||
|
renderDivs $
|
||||||
|
FileForm
|
||||||
|
<$> fileAFormReq "choose file"
|
||||||
|
|
||||||
|
instance RenderMessage Souplesse FormMessage where
|
||||||
|
renderMessage _ _ = defaultFormMessage
|
||||||
|
|
||||||
|
postUploadR :: Handler Html
|
||||||
|
postUploadR = do
|
||||||
|
((result, widget), enctype) <- runFormPost uploadForm
|
||||||
|
case result of
|
||||||
|
FormSuccess upload -> do
|
||||||
|
bs <- fileSourceByteString $ fileInfo upload
|
||||||
|
case Track.parseBS (fromStrict bs) of
|
||||||
|
Right points ->
|
||||||
|
defaultLayout [whamlet|<p>#{List.length points} points - thanks!|]
|
||||||
|
Left e ->
|
||||||
|
defaultLayout
|
||||||
|
[whamlet|<p>error ]
|
||||||
|
FormMissing ->
|
||||||
|
traceShow "missing" $
|
||||||
|
defaultLayout [whamlet|<p>missing|]
|
||||||
|
FormFailure x ->
|
||||||
|
traceShow x $
|
||||||
|
defaultLayout
|
||||||
|
[whamlet|
|
||||||
|
<p>Nope, sorry
|
||||||
|
|]
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
|
@ -11,17 +11,18 @@ module Track
|
|||||||
time,
|
time,
|
||||||
parse,
|
parse,
|
||||||
parseFile,
|
parseFile,
|
||||||
|
parseBS,
|
||||||
Track.length,
|
Track.length,
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
|
import Data.Either
|
||||||
import Data.Functor ((<&>))
|
import Data.Functor ((<&>))
|
||||||
import Data.List as List
|
import Data.List as List
|
||||||
import Data.List qualified
|
import Data.List qualified
|
||||||
import Data.Map as Map
|
import Data.Map as Map
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Either
|
|
||||||
import Data.Text qualified
|
import Data.Text qualified
|
||||||
import Data.Text.Lazy as T
|
import Data.Text.Lazy as T
|
||||||
import Data.Time
|
import Data.Time
|
||||||
@ -119,3 +120,7 @@ parseFile name = do
|
|||||||
return $ case getPoints (fromDocument gpx) of
|
return $ case getPoints (fromDocument gpx) of
|
||||||
Left err -> []
|
Left err -> []
|
||||||
Right points -> points
|
Right points -> points
|
||||||
|
|
||||||
|
parseBS bs = do
|
||||||
|
gpx <- parseLBS def bs
|
||||||
|
getPoints (fromDocument gpx)
|
||||||
|
@ -71,8 +71,11 @@ executable souplesse
|
|||||||
build-depends:
|
build-depends:
|
||||||
base ^>=4.18.2.1
|
base ^>=4.18.2.1
|
||||||
, souplesse-lib
|
, souplesse-lib
|
||||||
|
, text
|
||||||
|
, bytestring
|
||||||
, yesod-core == 1.6.25.1
|
, yesod-core == 1.6.25.1
|
||||||
, yesod-static
|
, yesod-static
|
||||||
|
, yesod-form
|
||||||
|
|
||||||
-- Directories containing source files.
|
-- Directories containing source files.
|
||||||
hs-source-dirs: app
|
hs-source-dirs: app
|
||||||
|
Loading…
Reference in New Issue
Block a user