Skip to content

Instantly share code, notes, and snippets.

View acfoltzer's full-sized avatar
💭
I may be slow to respond.

Adam C. Foltzer acfoltzer

💭
I may be slow to respond.
View GitHub Profile
% mv
File "/bin/mv", line 6
SyntaxError: Non-ASCII character '\xc2' in file /bin/mv on line 6, but no encoding declared; see http://www.python.org/peps/pep-0263.html for details
@acfoltzer
acfoltzer / ConsList.hs
Created April 30, 2013 20:00
Example of view patterns + typeclasses for polymorphic "constructors"
{-# LANGUAGE ViewPatterns #-}
import Data.Vector (Vector)
import qualified Data.Vector as V
data ConsView a = Nil | Cons a (ConsView a)
deriving (Eq, Ord, Show)
class ConsList l where
viewCons :: l a -> ConsView a
{-# LANGUAGE NoMonomorphismRestriction #-}
import Data.Map as Map
import Prelude as P
-- When there's a name clash, you can use the qualifier
mapNull = Map.null
listNull = P.null
-- When a name is unambiguous, you can just use it
mapMember = member
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ConstraintKinds #-}
import Control.Applicative
import Control.Monad.State
data Var = Var
@acfoltzer
acfoltzer / gist:2926368
Created June 13, 2012 20:33
Listings settings for Haskell
\lstnewenvironment{code}
{\lstset{}%
\csname lst@SetFirstLabel\endcsname}
{\csname lst@SaveFirstLabel\endcsname}
\lstset{
language=Haskell,
basicstyle=\small\ttfamily,
flexiblecolumns=false,
basewidth={0.5em,0.45em},
% keywordstyle=\color{blue},
@acfoltzer
acfoltzer / Affinity.hs
Created March 9, 2012 05:42
Haskell affinity
{-# LANGUAGE ForeignFunctionInterface #-}
module System.Posix.Affinity (setAffinityOS) where
import Control.Monad
import Foreign
import Foreign.C
import System.IO.Error
foreign import ccall unsafe "pin_pthread" pin_pthread :: CInt -> IO Errno
@acfoltzer
acfoltzer / radix_acc.hs
Created March 5, 2012 14:40
Radix sort kaboom
afoltzer@beetle ~/src/monad-par/examples [meta*]$ ghc-pkg list | grep accelerate
accelerate-0.9.0.1
afoltzer@beetle ~/src/monad-par/examples [meta*]$ ghc --make -O2 radix_acc.hs
[1 of 1] Compiling Main ( radix_acc.hs, radix_acc.o )
radix_acc.hs:19:1:
Warning: In the use of `M.unsafeFreeze'
(imported from Data.Array.MArray):
Deprecated: "Please import from Data.Array.Unsafe instead; This will be removed in the next release"
Linking radix_acc ...
@acfoltzer
acfoltzer / Vector.hs
Created March 1, 2012 05:10
Prototype Accelerate Vector conversions
{-# LANGUAGE CPP, TypeFamilies #-}
{-# OPTIONS_GHC -Wall #-}
-- | Helpers for fast conversion of 'Data.Vector.Storable' vectors
-- into Accelerate arrays.
module Data.Array.Accelerate.IO.Vector where
import Data.Array.Accelerate ( arrayShape
, Array
, DIM1
@acfoltzer
acfoltzer / amb.scm
Created February 21, 2012 22:20
amb with ivars
;; Adam Foltzer
;; amb with ivars
(load "pmatch.scm")
;;;; Global scheduler queue and helpers; ugly!
(define *q* '())
(define push-right!
(lambda (x)
@acfoltzer
acfoltzer / FixFact.hs
Created January 12, 2012 01:15
Fix at work
fix :: (a -> a) -> a
fix f = f (fix f)
fact' :: (Integer -> Integer) -> Integer -> Integer
fact' = \bang -> \n -> if n == 0 then 1 else n * bang (n-1)
fact :: Integer -> Integer
fact = fix fact'
onehundredandtwenty :: Integer