Last active
December 29, 2025 01:39
-
-
Save LSLeary/caf48686f39fce693bfe85546aafbc25 to your computer and use it in GitHub Desktop.
Church-encoded lists for constant-space enumeration (experimental)
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, TypeFamilies, LambdaCase, BlockArguments #-} | |
| module Enumeration ( | |
| Enumeration(..), | |
| fromFoldable, | |
| ) where | |
| -- GHC/base | |
| import GHC.Exts (build) | |
| import GHC.IsList (IsList(..)) | |
| -- base | |
| import Data.Foldable (Foldable(toList)) | |
| import Control.Applicative (Alternative(..)) | |
| newtype Enumeration a = MkEnumeration{ | |
| unMkEnumeration :: forall r. (a -> r -> r) -> r -> r | |
| } deriving Functor | |
| instance Foldable Enumeration where | |
| {-# INLINE foldr #-} | |
| foldr f z xs = unMkEnumeration xs f z | |
| {-# INLINE toList #-} | |
| toList = enumToList | |
| instance Applicative Enumeration where | |
| {-# INLINE pure #-} | |
| pure x = MkEnumeration \cons nil -> cons x nil | |
| {-# INLINE liftA2 #-} | |
| liftA2 f xs ys = MkEnumeration \cons nil -> | |
| unMkEnumeration xs (\x -> unMkEnumeration ys (cons . f x)) nil | |
| instance Alternative Enumeration where | |
| empty = MkEnumeration \_ nil -> nil | |
| xs <|> ys = MkEnumeration \cons nil -> | |
| unMkEnumeration xs cons (unMkEnumeration ys cons nil) | |
| instance Monad Enumeration where | |
| xs >>= k = MkEnumeration \cons nil -> | |
| unMkEnumeration xs (\x -> unMkEnumeration (k x) cons) nil | |
| instance IsList (Enumeration a) where | |
| type Item (Enumeration a) = a | |
| {-# INLINE fromList #-} | |
| fromList = fromFoldable | |
| {-# INLINE toList #-} | |
| toList = enumToList | |
| {-# INLINE enumToList #-} | |
| enumToList :: Enumeration a -> [a] | |
| enumToList xs = build (unMkEnumeration xs) | |
| {-# INLINE fromFoldable #-} | |
| fromFoldable :: Foldable f => f a -> Enumeration a | |
| fromFoldable xs = MkEnumeration \cons nil -> foldr cons nil xs |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment