Skip to content

Instantly share code, notes, and snippets.

View 3noch's full-sized avatar
🕯️

Elliot Cameron 3noch

🕯️
  • Indiana
View GitHub Profile
@3noch
3noch / PreventDefault.hs
Created December 19, 2017 19:08
Reflex-DOM preventDefault
module App.Front.Lib.Dom (
elDynAttrWithPreventDefaultEvent',
elDynAttrWithModifyConfig'
) where
import Control.Lens ((%~), (.~))
import Data.Map (Map)
import Data.Proxy (Proxy(..))
import Data.Text (Text)
import Reflex.Dom.Core
@3noch
3noch / BigTypeSig.hs
Created December 15, 2017 20:41
Large type sig
leadPropertyFilters :: (Columnar f0 Int
~
QGenExpr context syntax s t,
HaskellLiteralForQExpr a ~ Int,
Columnar f0 Bool ~ QGenExpr context syntax s Bool,
Columnar f0 (Maybe Int) ~ QGenExpr context syntax s a1,
Columnar f0 Text ~ QGenExpr context syntax s a4,
Columnar f0 (Auto Int) ~ QGenExpr context syntax s (Auto a3),
Database.Beam.Backend.SQL.SQL92.IsSql92ExpressionSyntax syntax,
SqlOrd
{ config
, pkgs
, lib
, ...
}:
let
cfg = config.simpleWebServer;
in with lib; {
@3noch
3noch / DrifterProjectM36.hs
Last active September 12, 2017 18:14
ProjectM36 Migrations with Drifter
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Db.Migration
( Method(..)
, PM36Migration
, Table, Uniqueness(..)
, defineTableIfNotExists
@3noch
3noch / build.sh
Created September 12, 2017 04:30
project-m36.nix
nix-build project-m36.nix
# to open a shell where cabal works
nix-shell -E '(import ./project-m36.nix {}).env'
# cabal build
@3noch
3noch / Route.hs
Created August 15, 2017 13:14
Router
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
@3noch
3noch / .ghci
Last active October 29, 2018 09:49
Reflex-DOM Auto Reload Development with ghcid
:set prompt "> "
:set -isrc
:load Main
@3noch
3noch / TextInsert.hs
Created August 9, 2017 23:33
Text Insert Reflex-DOM
{-# LANGUAGE RecursiveDo, TemplateHaskell, FlexibleContexts, TypeFamilies, OverloadedStrings #-}
import Control.Monad
import Control.Lens
import Reflex.Dom
import Reflex.Dom.Widget.Input
import qualified GHCJS.DOM.HTMLInputElement as J
import qualified GHCJS.DOM.Element as J
import Data.FileEmbed
import qualified Data.Text as T
@3noch
3noch / OpenGADT.hs
Created August 6, 2017 04:09
Function Application at Type Level (a.k.a. Open GADT)
{-# LANGUAGE PolyKinds, TypeFamilies, TypeOperators #-}
type family ($) (f :: k1) (x :: k2) :: k3
data Id
type instance Id $ x = x
data DoSomething
type instance DoSomething $ x = Either x x
@3noch
3noch / latestLeft.hs
Last active July 6, 2017 18:25
Reflex Function: latestLeft
latestLeft :: (Reflex t, MonadHold t m) => a -> Event t (Either a b) -> m (Dynamic t a)
latestLeft initial x = holdDyn initial $ fmapMaybe (either Just (const Nothing)) x