Skip to content

Instantly share code, notes, and snippets.

@shamansir
Last active June 18, 2019 12:10
Show Gist options
  • Save shamansir/ef3dd964769e960c19f5ca45fa8e84f8 to your computer and use it in GitHub Desktop.
Save shamansir/ef3dd964769e960c19f5ca45fa8e84f8 to your computer and use it in GitHub Desktop.
msg: MsgOne {}
uuid: '336228ee-b2e8-4c78-acf4-a8302125552b'
(MSG-ONE:336228ee-b2e8-4c78-acf4-a8302125552b)-|
msg: MsgTwo {}
uuid: 'cbfeae0b-11f1-4e58-a4f9-35bab61bdbf2'
uuid: '7965f57f-cde5-4ca5-8377-bd03b9c71784'
(MSG-TWO:7965f57f-cde5-4ca5-8377-bd03b9c71784)-(MSG-ONE:cbfeae0b-11f1-4e58-a4f9-35bab61bdbf2)-|
msg: MsgTwo {}
uuid: '256702ea-6702-4aa2-84c0-3977e1763e8'
uuid: 'fd7bdf0d-6f6b-46d2-b394-f268c4c5a473'
uuid: '2bea4621-873a-47f5-9803-0da53e5dc34f'
(MSG-TWO:2bea4621-873a-47f5-9803-0da53e5dc34f)-(MSG-TWO:fd7bdf0d-6f6b-46d2-b394-f268c4c5a473)-(MSG-ONE:256702ea-6702-4aa2-84c0-3977e1763e82)-|
module TestMUV where
import Prelude
import Effect (Effect)
import Effect.Class (liftEffect)
import Effect.Console (log)
import Data.Either (Either, either)
import Control.Monad.Except.Trans (ExceptT, runExceptT)
import FRP.Event (Event)
import FRP.Event as Event
import Debug.Trace as DT
import UUID as UUID
data Error = Error String
type Program a = ExceptT Error Effect a
data Msg = MsgOne | MsgTwo
instance showMsg :: Show Msg where
show MsgOne = "MSG-ONE"
show MsgTwo = "MSG-TWO"
runMUV
:: forall model view
. Event Msg
-> Program model
-> (Msg -> Program model -> Program model)
-> (Either Error model -> view)
-> Event (Effect view)
runMUV messages init userUpdate userView =
let
updates = Event.fold update messages init
views = view <$> updates
in views
where
update :: Msg -> Program model -> Program model
update msg model =
let _ = DT.spy "msg" msg
in userUpdate msg model
view :: Program model -> Effect view
view program =
userView <$> runExceptT program
main :: Effect Unit
main = do
{ event : messages, push } <- Event.create
let views = runMUV messages (pure "|") update view
_ <- Event.subscribe views \effV -> effV >>= log
push MsgOne
push MsgTwo
push MsgTwo
pure unit
where
update msg model =
model >>= \prev -> do
uuid <- liftEffect UUID.new
let _ = DT.spy "uuid" uuid
pure $ "(" <> show msg <> ":" <> UUID.toString uuid <> ")-" <> prev
view errOrModel =
either (const "ERR") identity errOrModel
"use strict";
/**
* Fast UUID generator, RFC4122 version 4 compliant.
* @author Jeff Ward (jcward.com).
* @license MIT license
* @link http://stackoverflow.com/questions/105034/how-to-create-a-guid-uuid-in-javascript/21963136#21963136
**/
var UUID = (function() {
var self = {};
var lut = []; for (var i=0; i<256; i++) { lut[i] = (i<16?'0':'')+(i).toString(16); }
self.generate = function() {
var d0 = Math.random()*0xffffffff|0;
var d1 = Math.random()*0xffffffff|0;
var d2 = Math.random()*0xffffffff|0;
var d3 = Math.random()*0xffffffff|0;
return lut[d0&0xff]+lut[d0>>8&0xff]+lut[d0>>16&0xff]+lut[d0>>24&0xff]+'-'+
lut[d1&0xff]+lut[d1>>8&0xff]+'-'+lut[d1>>16&0x0f|0x40]+lut[d1>>24&0xff]+'-'+
lut[d2&0x3f|0x80]+lut[d2>>8&0xff]+'-'+lut[d2>>16&0xff]+lut[d2>>24&0xff]+
lut[d3&0xff]+lut[d3>>8&0xff]+lut[d3>>16&0xff]+lut[d3>>24&0xff];
}
return self;
})();
exports.newAsString = function() {
return UUID.generate();
}
module UUID
( UUID
, new
, toString
) where
import Prelude
import Data.Maybe (Maybe(..))
import Effect (Effect)
foreign import newAsString :: Effect String
newtype UUID = UUID String
derive instance eqUuid :: Eq UUID
derive instance ordUuid :: Ord UUID
new :: Effect UUID
new = newAsString <#> UUID
toString :: UUID -> String
toString (UUID uuid) = uuid
instance showUUID :: Show UUID where
show (UUID uuid) = "{" <> uuid <> "}"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment