Last active
June 19, 2016 23:14
-
-
Save afldcr/1586c6ec23556aa1000170a22e8cdbbe to your computer and use it in GitHub Desktop.
Sets can be a functor in Haskell, too. They just aren't.
This file contains hidden or 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
| {-# LANGUAGE RankNTypes #-} | |
| import Control.Monad.State (State, gets, put) | |
| import Data.Set (Set) | |
| import qualified Data.Set as S | |
| newtype SetF a = | |
| SetF (forall x. Ord x => (a -> x) -> Set x) | |
| instance Ord a => Eq (SetF a) where | |
| x == y = unlift x == unlift y | |
| instance Functor SetF where | |
| fmap fn (SetF run) = | |
| SetF $ \tf -> run (tf . fn) | |
| lift :: Set a -> SetF a | |
| lift s = SetF $ \tf -> foldr (\x -> S.insert (tf x)) S.empty s | |
| unlift :: Ord a => SetF a -> Set a | |
| unlift (SetF run) = run id | |
| insert,delete :: Ord a => a -> SetF a -> SetF a | |
| insert val = lift . S.insert val . unlift | |
| delete val = lift . S.delete val . unlift | |
| taps :: Ord a => (Set a -> b) -> State (SetF a) b | |
| taps fn = do s <- gets unlift | |
| put (lift s) | |
| pure (fn s) | |
| member :: Ord a => a -> State (SetF a) Bool | |
| member x = taps (S.member x) | |
| size :: Ord a => State (SetF a) Int | |
| size = taps S.size |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment