Skip to content

Instantly share code, notes, and snippets.

View m-renaud's full-sized avatar

Matt Renaud m-renaud

  • Google Inc.
  • San Francisco, CA
View GitHub Profile
@m-renaud
m-renaud / FastParse.hs
Last active August 29, 2015 14:10
Fast Int Parsing
{-# LANGUAGE BangPatterns #-}
module FastParse (parseInts) where
import Prelude hiding (length)
import Control.Applicative hiding (empty)
import Control.Monad
import Data.Char
import Data.Maybe
import Data.Sequence
@m-renaud
m-renaud / IntParse.hs
Last active August 29, 2015 14:10
Int parsing and simple operation
{-# LANGUAGE BangPatterns #-}
{-# OPTIONS_GHC -Odph #-}
import qualified Data.ByteString.Char8 as S
import qualified Data.Vector as U
-- Read ints from stdin into a vector then print the length.
main = S.getContents >>= print . U.length . parse
-- Fill a new vector from a file containing a list of numbers.
@m-renaud
m-renaud / SumOfSquaresStreamFusion.hs
Created November 22, 2014 09:29
Sum of squares. This contains two versions, one using Vector and another that takes advantage of stream fusion. The stream fusion version is sightly faster and uses constant space. You'll ALSO notice, the only difference between the two files is the 3rd import statement :)
{-# LANGUAGE BangPatterns #-}
{-# OPTIONS_GHC -Odph #-}
import Prelude hiding (map, sum)
import qualified Data.ByteString.Char8 as S
import Data.List.Stream
main = S.getContents >>= print . sumOfSquares . parse
where sumOfSquares = sum . map (\x -> x * x)
@m-renaud
m-renaud / ParseUriQuery.hs
Last active August 29, 2015 14:10
Parse the query component of a URI.
module ParseUriQuery where
import Control.Applicative
import Data.Attoparsec.ByteString.Char8
import Data.ByteString.Char8 (ByteString, pack, unpack)
import Data.Either
data QueryTerm = QueryTerm { termName :: ByteString
, termValue :: Maybe ByteString
} deriving (Eq, Read, Show)
@m-renaud
m-renaud / .inputrc
Created December 4, 2014 19:26
Ergonomic keyboard mappings.
set bind-tty-special-chars off
Control-h: backward-char
"\eh": backward-word
Control-t: previous-history
Control-n: next-history
Control-s: forward-char
"\es": forward-word
;;; Ergonomic changes.
;;; These are for the Dvorak keyboard layout.
(defvar mrenaud-ergo-minor-mode-map (make-keymap) "mrenaud-ergo-minor-mode keymap.")
;; Movement commands:
;; Now lie on right hand homerow.
;; h t n s
;; < ^ v >
(define-key mrenaud-ergo-minor-mode-map (kbd "C-h") 'backward-char)
@m-renaud
m-renaud / GenericGraph.hs
Last active February 27, 2016 19:50
Generic graphs with type families instead of functional dependencies.
{- | Based on http://www.osl.iu.edu/publications/prints/2005/garcia05:_extended_comparing05.pdf -}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
import Data.Array
----------------------------------------
-- Typeclass definitions.
@m-renaud
m-renaud / git-codegen-in-branch.bash
Last active November 4, 2016 00:44
Git commands for building generated files on another branch and pulling them in temporarily for a build
#!/bin/bash
# Save the current branch.
previous_branch=`git rev-parse --abbrev-ref HEAD`
# Switch to generated code branch and pull in any changes from the working branch.
git checkout generated-code
git merge --no-edit $previous_branch
# <Build generated files>
@m-renaud
m-renaud / custom-decoder.elm
Created November 15, 2016 18:11
Custom decoder in elm 0.18
customDecoder decoder toResult =
Json.andThen
(\a ->
case toResult a of
Ok b -> Json.succeed b
Err err -> Json.fail err
)
decoder
@m-renaud
m-renaud / mrenaud-helm.el
Last active January 12, 2017 00:02
Helm config
(require 'helm-config)
(require 'helm-ls-git)
(require 'helm-swoop)
(helm-mode)
;; Interactive buffer rebindings.
(define-key helm-map (kbd "<tab>") 'helm-execute-persistent-action)
(define-key helm-map (kbd "C-i") 'helm-execute-persistent-action)
(define-key helm-map (kbd "C-z") 'helm-select-action)