Skip to content

Instantly share code, notes, and snippets.

@nebuta
Last active August 29, 2015 13:57
Show Gist options
  • Save nebuta/9556655 to your computer and use it in GitHub Desktop.
Save nebuta/9556655 to your computer and use it in GitHub Desktop.
Delaunay triangulation that runs as a service
{-# LANGUAGE OverloadedStrings #-}
import Graphics.Triangulation.Delaunay
import Data.Vector.V2
import Data.Aeson
import Data.ByteString (ByteString)
import Data.Text.Lazy.Encoding (encodeUtf8)
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as TL
import Web.Scotty
import Control.Monad.Trans (liftIO)
-- import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BL
type Triangle = (Vector2, Vector2, Vector2)
-- dat :: [Vector2]
-- dat = map (uncurry Vector2) [(1,2),(2,3),(2,5),(1,6)]
-- res :: [Triangle]
-- res = triangulate dat
conv :: Triangle -> Value
conv (Vector2 x1 y1, Vector2 x2 y2, Vector2 x3 y3) =
toJSON [x1,y1,x2,y2,x3,y3]
main = scotty 3000 $ do
post "/programming/delaunay" $ do
p <- param "data"
j <- param "json"
liftIO $ print p
let f = if j == (1 :: Int) then Web.Scotty.json . map conv else csv
case decode (encodeUtf8 p) of
Just dat -> f $ triangulate $ map pnt dat
_ -> Web.Scotty.text "[]"
csv :: [Triangle] -> ActionM ()
csv ts = Web.Scotty.text txt
where
txt = TL.intercalate "\n" $ map c ts
c (Vector2 x1 y1, Vector2 x2 y2, Vector2 x3 y3)
= TL.intercalate "," $ map (TL.pack . show) [x1,y1,x2,y2,x3,y3]
pnt [a,b] = Vector2 a b
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment