Skip to content

Instantly share code, notes, and snippets.

@jrp2014
jrp2014 / WC.hs
Last active June 29, 2019 21:29
The Essence of the Iterator Pattern
{-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE ScopedTypeVariables #-}
module WC where
import Control.Applicative -- WrappedMonad
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
module TNumber where
import Text.Pretty.Simple
import Control.Monad.State
-- https://stackoverflow.com/questions/44784899/how-to-write-function-for-n-ary-tree-traversal-in-haskell?rq=1
data NT a = N a [NT a] deriving (Show, Functor, Foldable, Traversable)
module Fox where
-- http://blog.sigfpe.com/2007/01/foxs-ubiquitous-free-derivative-pt-2.html
--
import Prelude hiding ( (<*>) )
import Data.List
data RE a
= Symbol a
| Star (RE a)
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PatternSynonyms #-}
module Alopegmorphism where
import Data.Void
type Triple = I :*: I :*: I
{-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE PatternSynonyms #-}
module Cojoingrids where
module ListZipper where
-- http://blog.emillon.org/posts/2012-10-18-comonadic-life.html
import Control.Comonad
import GHC.Base
data ListZipper a =
LZ [a]
a
[a]
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE LambdaCase #-}
-- https://stackoverflow.com/questions/10239630/where-to-find-programming-exercises-for-applicative-functors/10242673
-- https://github.com/pigworker/WhatRTypes4/blob/master/Types4.hs
--
module Triple where
import Control.Applicative
import Data.Char
@jrp2014
jrp2014 / # macvim - 2018-04-21_11-29-56.txt
Created April 21, 2018 10:30
macvim on macOS 10.13.4 - Homebrew build logs
Homebrew build logs for macvim on macOS 10.13.4
Build date: 2018-04-21 11:29:56
@jrp2014
jrp2014 / # macvim - 2018-04-21_11-10-25.txt
Created April 21, 2018 10:24
macvim on macOS 10.13.4 - Homebrew build logs
Homebrew build logs for macvim on macOS 10.13.4
Build date: 2018-04-21 11:10:25