Skip to content

Instantly share code, notes, and snippets.

View oliver-batchelor's full-sized avatar

Oliver Batchelor oliver-batchelor

  • University of Canterbury
  • Christchurch, New Zealand
View GitHub Profile
@oliver-batchelor
oliver-batchelor / 1_readme.md
Created June 13, 2012 17:44 — forked from geelen/1_readme.md
AngularJS and Coffeescript
@oliver-batchelor
oliver-batchelor / 1_readme.md
Created June 14, 2012 02:33 — forked from geelen/1_readme.md
Tree edit

Running Gists like a JsFiddle

TL;DR: This page (html, css, javascript, markdown) is being served from this gist using this server.

After working with AngularJS, which is totally awesome, I wanted a better way to share code snippets with the community. Something where the header declarations aren't hidden, so it's clear which version of angular you're using and whether zepto/jquery/underscore are loaded. I also wanted to use CoffeeScript, HAML and SCSS because that's what I use to write Goodfilms (my day job).

This HTML is being rendered from HAML, the CSS is being compiled from SCSS, the JS code is written in Coffeescript and even this here text is being compiled (in the browser) from a gist-hosted Markdown file.

{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
@oliver-batchelor
oliver-batchelor / Tensor.hs
Last active October 2, 2016 23:55
Attempts at static tensor dimensioning
{-# LANGUAGE TemplateHaskell, FlexibleContexts, FlexibleInstances, GADTs, DataKinds,
TypeInType, KindSignatures, InstanceSigs, TypeOperators,
ConstraintKinds, RankNTypes, ScopedTypeVariables, TypeFamilies,
UndecidableInstances, MultiParamTypeClasses, TypeApplications, PartialTypeSignatures #-}
--{-# OPTIONS_GHC -fplugin GHC.TypeLits.Normalise -fplugin GHC.TypeLits.KnownNat.Solver #-}
-- Three attempts at implementing a 'concat' operation for arbitrary dimension tensors,
-- concat dim xs ys is valid only if tensor xs and tensor ys share the same shape
-- (except for the dimension being joined)
{-# LANGUAGE TemplateHaskell, FlexibleContexts, FlexibleInstances, GADTs, DataKinds,
TypeInType, KindSignatures, InstanceSigs, TypeOperators,
ConstraintKinds, RankNTypes, ScopedTypeVariables, TypeFamilies,
UndecidableInstances, MultiParamTypeClasses, TypeApplications, PartialTypeSignatures #-}
$(singletons [d|
data UNat = Zero | Succ UNat
deriving (Eq)
|])
import Data.Type.Index
data Sum :: [Type] -> Type where
L :: x -> Sum (x : xs)
R :: Sum xs -> Sum (x : xs)
inj :: (Elem xs x) => x -> Sum xs
inj = inj' elemIndex
module SumF where
import GHC.Generics (Generic1)
import Data.Kind (Type, Constraint)
import Data.Proxy
import Data.Functor.Classes
timeout :: MonadWidget t m => (Event t a, Event t a) -> NominalDiffTime -> m (Event t a)
timeout (down, up) time = do
delayed <- delay time down
let timedOut = flip pushAlways down $ const $ mdo
isDown <- hold True (False <$ leftmost [up, delayed])
return $ gate isDown delayed
switchHold never timedOut
data ApplyKey b a where
F :: ApplyKey (a -> b)
A :: ApplyKey a