Last active
October 9, 2015 14:39
-
-
Save larsrh/eaa7ef599dcd81538b1c to your computer and use it in GitHub Desktop.
Haskell collection redesign
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- Joke implementation of a joke idea | |
-- Scala-2.8-style collections in Haskell | |
{-# LANGUAGE FlexibleInstances #-} | |
{-# LANGUAGE FlexibleContexts #-} | |
{-# LANGUAGE MultiParamTypeClasses #-} | |
{-# LANGUAGE TypeFamilies #-} | |
{-# LANGUAGE FunctionalDependencies #-} | |
{-# LANGUAGE GeneralizedNewtypeDeriving #-} | |
{-# LANGUAGE DefaultSignatures #-} | |
{-# LANGUAGE ScopedTypeVariables #-} | |
import Control.Monad (when) | |
import Control.Monad.Trans | |
import Control.Monad.Trans.State | |
import Data.Foldable (traverse_) | |
import qualified Data.Set as S | |
import Data.Proxy | |
class Monad m => MonadBuilder m a where | |
append :: a -> m () | |
class MonadBuilder m (Elem coll) => HasBuilder m coll | coll -> m where | |
newBuilder :: proxy coll -> m () | |
runBuilder :: m () -> coll | |
class Collection coll where | |
type Elem coll :: * | |
foreach :: Monad m => (Elem coll -> m ()) -> coll -> m () | |
default foreach :: (Monad m, coll ~ f (Elem coll), Foldable f) => (Elem coll -> m ()) -> coll -> m () | |
foreach = traverse_ | |
mapTo :: (Collection coll, HasBuilder m coll') => proxy coll' -> (Elem coll -> Elem coll') -> coll -> coll' | |
mapTo proxy f coll = runBuilder $ do | |
newBuilder proxy | |
foreach (append . f) coll | |
dropTo :: (Collection coll, HasBuilder m coll', Elem coll' ~ Elem coll) => proxy coll' -> Integer -> coll -> coll' | |
dropTo proxy n coll = runBuilder $ do | |
newBuilder proxy | |
evalStateT (foreach f coll) n | |
where f elem = do | |
m <- get | |
when (m <= 0) $ lift $ append elem | |
modify (\x -> x - 1) | |
return () | |
size :: Collection coll => coll -> Integer | |
size coll = execState (foreach (const $ modify succ) coll) 0 | |
instance Collection [a] where | |
type Elem [a] = a | |
instance Collection (S.Set a) where | |
type Elem (S.Set a) = a | |
newtype ListBuilder elem a = ListBuilder (State [elem] a) | |
deriving (Functor, Applicative, Monad) | |
instance MonadBuilder (ListBuilder elem) elem where | |
append x = ListBuilder $ modify (x:) | |
instance HasBuilder (ListBuilder elem) [elem] where | |
newBuilder _ = ListBuilder $ put [] | |
runBuilder (ListBuilder s) = reverse $ execState s undefined | |
instance Ord elem => HasBuilder (ListBuilder elem) (S.Set elem) where | |
newBuilder _ = ListBuilder $ put [] | |
runBuilder (ListBuilder s) = S.fromList $ execState s undefined |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment
Example usage: