Skip to content

Instantly share code, notes, and snippets.

@sjoerdvisscher
Created October 8, 2011 10:47
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save sjoerdvisscher/1272128 to your computer and use it in GitHub Desktop.
Save sjoerdvisscher/1272128 to your computer and use it in GitHub Desktop.
μx. β + (α → x) is an isotope of Stream α → β
{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
import Data.Stream.Infinite
import Control.Applicative
import Data.Key
import Data.Distributive
import Data.Functor.Bind
import Data.Functor.Representable
import Data.Unamb
-- The Key type instance of Free f a from the free package is Seq a which does not work
data Free f a = Pure a | Free (f (Free f a))
type instance Key (Free ((->) a)) = Stream a
instance Representable (Free ((->) a)) where
-- This is not unambiguous choice, but the ambiguity is not really relevant.
tabulate f = Pure (f und) `unamb` Free (\a -> tabulate (\s -> f (a :> s)))
where
und = und
instance Indexable (Free ((->) a)) where
index (Pure b) _ = b
index (Free f) (a :> as) = index (f a) as
instance Lookup (Free ((->) a)) where lookup = lookupDefault
instance Functor (Free ((->) a)) where fmap = fmapRep
instance Keyed (Free ((->) a)) where mapWithKey = mapWithKeyRep
instance Distributive (Free ((->) a)) where distribute = distributeRep
instance Zip (Free ((->) a)) where zipWith = zipWithRep
instance ZipWithKey (Free ((->) a)) where zipWithKey = zipWithKeyRep
instance Apply (Free ((->) a)) where (<.>) = apRep
instance Applicative (Free ((->) a)) where { pure = pureRep; (<*>) = apRep }
three :: Stream a -> [a]
three (a :> b :> c :> _) = [a, b, c]
test :: [Int]
test = index (tabulate three :: Free ((->) Int) [Int]) (fromList [0..])
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment