Skip to content

Instantly share code, notes, and snippets.

View ChrisPenner's full-sized avatar
:bowtie:
Happily Hacking

Chris Penner ChrisPenner

:bowtie:
Happily Hacking
View GitHub Profile
@ChrisPenner
ChrisPenner / ChooseIndex.hs
Created September 14, 2019 18:01
Gain extra context in your lens chain by passing values as an index!
Sometimes when diving deep with optics you need to reference something earlier in your path after you dive deeper. Just stash it in your index!
Let's say we want to know which pets belong to which owner, we've got the data paired up like this:
pets :: [(String, [String])]
pets =
[ ("Steven", ["Spot", "Mittens"])
, ("Kaylee", ["Pepper", "Sparky"])
]
@ChrisPenner
ChrisPenner / LensyBinarySearch.hs
Created August 27, 2019 05:36
Binary tree search using lenses
-- Define a simple binary tree
data BT a
= BT { _leftTree :: BT a
, _val :: a
, _rightTree :: BT a
}
| Leaf
deriving (Show, Eq, Functor, Foldable, Traversable)
-- Generate traversals for the (partial) fields
makeLenses ''BT
@ChrisPenner
ChrisPenner / FindIslands.hs
Last active August 23, 2019 16:09
A quick experiment using union-find to determine which pieces of 'land' in a grid are connected. Could ostensibly be used with any equivalence/grouping predicate.
{-# LANGUAGE ScopedTypeVariables #-}
module Lib where
import Data.UnionFind.IO
import Control.Monad
import Control.Applicative
import Data.Foldable
import Data.Maybe
import qualified Data.Map as M
import qualified Data.Set as S
@ChrisPenner
ChrisPenner / DynamicComonad.hs
Created April 5, 2019 20:22
Dynamic Programming Comonads using Recursion Schemes
import Data.Functor.Foldable
import Control.Comonad.Cofree as C
import Control.Comonad.Trans.Cofree as CF
cofreeDynExtend :: forall f a b.
Functor f
=> (CofreeF f a (C.Cofree f b) -> b)
-> C.Cofree f a
-> C.Cofree f b
cofreeDynExtend f = cata extract'
@ChrisPenner
ChrisPenner / GenericMonoid.hs
Last active February 22, 2019 19:51
Derive Monoid for using Generics
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DeriveGeneric #-}
module GenericMonoid where
import Data.Monoid
import Data.Maybe
@ChrisPenner
ChrisPenner / matrix-search-comonad.hs
Last active November 12, 2018 20:47
Matrix path search using comonads
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Lib where
@ChrisPenner
ChrisPenner / update-monads.md
Created September 1, 2018 22:24
Update Monads

Today we're going to take a peek at the Update monad! It's a monad which was formalized and described in Update Monads: Cointerpreting Directed Containers by Danel Ahman and Tarmo Uustalu. Most folks probably haven't heard of it before, likely because most of what you'd use it for is well encompassed by the Reader, Writer, and State monads. The Update Monad can do everything that Reader, Writer, and State can do, but as a trade-off tends to be less efficient at each of those tasks. It's definitely still worth checking out though; not only is it interesting, there are a few things it handles quite elegantly that might be a bit awkward to do in other ways.

@ChrisPenner
ChrisPenner / README.md
Created June 3, 2018 00:31
Use Google Sheet as BigQuery Dataset

Generating BQ schema from google sheet header row

To generate a new schema:

  • Copy the ID header row from your google sheet

  • pbpaste | python make_schema.py

  • There's your BQ schema!

  • Add a new dataset to bigquery

  • Use your spreadsheet link as the file location

@ChrisPenner
ChrisPenner / custom-state-handlers.purs
Last active October 30, 2017 02:25
Custom State Handlers
module Main where
import Prelude
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE, log)
import Data.Either (Either(..))
import Data.Monoid (class Monoid, mempty)
import Run (Run, extract, lift, on, peel, send)
import Run.State (STATE, State(..))
@ChrisPenner
ChrisPenner / FreeMonadOptimization.hs
Last active August 24, 2017 02:18
Free Monads vs MTL regarding optimizations using AST transformations
{-# language DeriveFunctor #-}
{-# language GeneralizedNewtypeDeriving #-}
module FreeOpt where
import Control.Monad.Free
import Control.Monad.Trans
import System.Directory
-- | Define our Free Monad DSL
data FileF r =