This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE JavaScriptFFI #-} | |
{-# LANGUAGE OverloadedStrings #-} | |
{-# LANGUAGE TypeFamilies #-} | |
module Scorch.OCanvas | |
( | |
mkCanvas | |
, canvasDisplay | |
, canvasAddChild |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
mkCanvas' :: CanvasInfo -> IO (OCanvasRef) | |
mkCanvas' cnvInfo = do | |
cnvObj <- toJSRef cnvInfo | |
cnvRef <- js_create cnvObj | |
js_setWidth cnvRef (toJSInt $ width cnvInfo) | |
js_setHeight cnvRef (toJSInt $ height cnvInfo) | |
return cnvRef | |
mkCanvas :: (MonadWidget t m) => Event t CanvasInfo -> m (Event t OCanvasRef) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
listItemAttrDyn False = | |
"class" =: "list-item" | |
listItemAttrDyn True = | |
"class" =: "list-item highlight" | |
listItem :: (MonadWidget t m) => (String -> String) -> m (ListItem t) | |
listItem mkUrl = do | |
rec highlightDyn <- foldDyn (\a _ -> a) False highlightE | |
itemAttributesDyn <- mapDyn listItemAttrDyn highlightDyn |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE JavaScriptFFI #-} | |
module Scorch.GHCJS.File | |
( | |
readFileAsync | |
) where | |
import Control.Monad.Trans (liftIO) | |
import GHCJS.Types | |
import GHCJS.Foreign | |
import GHCJS.DOM.File (File) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
processEvent :: NE.NonEmpty ViewEvent -> EventState -> EventState | |
processEvent trigger (_, ij, nm) = | |
case NE.head trigger of | |
Init -> | |
(Just Refresh, ij, nm) | |
Prev -> | |
prevEvent ij nm | |
Next -> | |
nextEvent ij nm |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
;; base types | |
(defvar *regex-null* nil) | |
(defvar *regex-empty* t) | |
;; predicates | |
(defun regex-alt? (re) | |
(and (consp re) (eq (car re) 'alt))) | |
(defun regex-seq? (re) | |
(and (consp re) (eq (car re) 'seq))) | |
(defun regex-rep? (re) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
;; Examples | |
;;------------------------------------------------------------------------------ | |
;; 1. non-commands | |
;; There are two types of 'non-commands', | |
;; a) integers | |
;; b) symbols | |
;; | |
;; Symbols are looked up, so if you provide an initial environment, with a | |
;; symbol defined, it will be appropriately looked up. | |
;; e.g: (lookup 'x '((x . 0))) -> 0 |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
;; Examples | |
;;------------------------------------------------------------------------------ | |
;; 1. non-commands | |
;; There are two types of 'non-commands', | |
;; a) integers | |
;; b) symbols | |
;; | |
;; Symbols are looked up, so if you provide an initial environment, with a | |
;; symbol defined, it will be appropriately looked up. | |
;; e.g: (lookup 'x '((x . 0))) -> 0 |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
(defparameter *white-colour* #\O) | |
(defun make-image (m n) | |
(make-array (list m n) :initial-element *white-colour*)) | |
(defun clear (image) | |
(loop for i from 0 below (reduce #'* (array-dimensions image)) do | |
(setf (row-major-aref image i) *white-colour*))) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
;;------------------------------------------------------------------------------ | |
(eval-when (:compile-toplevel) | |
(ql:quickload :series)) | |
(defpackage luhn | |
(:use :cl :series)) | |
(in-package :luhn) | |
;;-- sums integer digits as long as x is < 100. |