aboutsummaryrefslogtreecommitdiff
path: root/Handler/Home.hs
blob: 0ee0882b322308157a6342c60489b0ac6baa8dd2 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
{-# LANGUAGE TupleSections, OverloadedStrings #-}
module Handler.Home where

import Import

import qualified Data.Text as T
import Data.Aeson
import Text.Julius
import Yesod.WebSockets
import Turing.Examples
import Turing.Machine

data Cmd = Beginning | Backward | Forward | Poll | MHello | MSub deriving Read

data UpdM = UpdTape String | UpdTrans String | Stop
-- instance FromJSON UpdM where
--   parseJSON (Object v) = cons =<< (v .: "type")
--     where cons :: String -> Parser UpdM
--           cons t = (if t == "tape" then UpdTape else UpdTrans) <$> v .: "value"
--   parseJSON _ = mzero
instance ToJSON UpdM where
  toJSON um = object ["type" .= ty, "value" .= v]
    where (ty, v) = case um of
                     UpdTape s -> ("tape"::String, s)
                     UpdTrans s -> ("trans", s)
                     Stop -> ("stop", "")

wsTuring :: WebSocketsT Handler ()
wsTuring = startMachine mHello defaultConfig
    where startMachine m ic = do
            sendTextData . encode . UpdTrans . showTrans . trans $ m
            evalLoop m ic [ic]
          mHello = mWriteStr "Hello!"
          mSubConfig = mkConfig . map charToSym $ "_aaaaaa_aaa"
          defaultConfig = mkConfig . map charToSym $  "_"
          evalLoop m ic [] = evalLoop m ic [ic]
          evalLoop m ic cfgs@(c:cs) = do
            sendTextData . encode . UpdTape . show $ c
            cmd <- receiveData
            case (read . T.unpack $ cmd) of
              Beginning -> evalLoop m ic [ic]
              Backward -> evalLoop m ic cs
              Forward -> case step c (delta m) of
                           Just c' -> evalLoop m ic (c':cfgs)
                           Nothing -> do sendTextData . encode $ Stop
                                         evalLoop m ic cfgs
              Poll -> evalLoop m ic cfgs
              MHello -> startMachine mHello defaultConfig
              MSub -> startMachine mSub mSubConfig

getHomeR :: Handler Html
getHomeR = do
  webSockets wsTuring
  defaultLayout $ do
    setTitle "Turing simulator"

    -- JQuery
    addScriptRemote "https://ajax.googleapis.com/ajax/libs/jquery/2.1.1/jquery.min.js"
    -- Bootstrap CSS
    addStylesheetRemote "https://maxcdn.bootstrapcdn.com/bootstrap/3.2.0/css/bootstrap.min.css"
    -- Bootstrap JS
    addScriptRemote "https://maxcdn.bootstrapcdn.com/bootstrap/3.2.0/js/bootstrap.min.js"

    -- Identifiers used in HTML/JS code
    butBeginning <- newIdent
    butBackward <- newIdent
    butTogglePlay <- newIdent
    butForward <- newIdent
    prTape <- newIdent
    prTrans <- newIdent
    eHello <- newIdent
    eSub <- newIdent

    $(widgetFile "home")