Skip to content

Instantly share code, notes, and snippets.

@pdarragh
Created November 6, 2020 04:22
Show Gist options
  • Save pdarragh/2e495272b93393051bd45b23991144d7 to your computer and use it in GitHub Desktop.
Save pdarragh/2e495272b93393051bd45b23991144d7 to your computer and use it in GitHub Desktop.
Haskell implementations of Python's built-in Iterator, Iterable, and Sequence types and their associated functions
{-# LANGUAGE ConstrainedClassMethods #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
import Prelude hiding (all, any, length, map)
import Data.Bool (Bool(..), not, otherwise)
import Data.List (reverse)
import qualified Data.List (length)
class Iterator a where
type IteratorElement a :: *
next :: a -> Maybe (a, IteratorElement a)
newtype IteratorState a = NextIterator a
class Iterator (IteratorState a) => Iterable a where
type IterableElement a :: *
iter :: a -> IteratorState a
iter = NextIterator
all :: Boolifiable (IteratorElement (IteratorState a)) => a -> Bool
all as = allHelper (next (iter as)) where
allHelper Nothing = True
allHelper (Just (iterState, a))
| not (bool a) = False
| otherwise = allHelper (next iterState)
any :: Boolifiable (IteratorElement (IteratorState a)) => a -> Bool
any as = anyHelper (next (iter as)) where
anyHelper Nothing = False
anyHelper (Just (iterState, a))
| bool a = True
| otherwise = anyHelper (next iterState)
map :: (IteratorElement (IteratorState a) -> b) -> a -> [b]
map f as = mapHelper (next (iter as)) [] where
mapHelper Nothing bs = reverse bs
mapHelper (Just (iterState, a)) bs = mapHelper (next iterState) (f a : bs)
class Sequence a where
type SequenceElement a :: *
getitem :: a -> Int -> Maybe (SequenceElement a)
seqIter :: a -> IteratorState (a, Int)
seqIter xs = NextIterator (xs, 0)
class Lengthy a where
length :: a -> Int
instance Lengthy [a] where
length = Data.List.length
class Boolifiable a where
bool :: a -> Bool
instance Boolifiable Int where
bool 0 = False
bool _ = True
instance Boolifiable String where
bool "" = False
bool _ = True
instance Iterator (IteratorState [a]) where
type IteratorElement (IteratorState [a]) = a
next (NextIterator []) = Nothing
next (NextIterator (x:xs)) = Just (NextIterator xs, x)
instance Iterator (IteratorState a) => Iterator (IteratorState (IteratorState a)) where
type IteratorElement (IteratorState (IteratorState a)) = IteratorElement (IteratorState a)
next (NextIterator innerIterState) = case next innerIterState of
Nothing -> Nothing
Just (nextInnerIterState, element) -> Just (NextIterator nextInnerIterState, element)
instance Iterator (IteratorState a) => Iterable (IteratorState a) where
type IterableElement (IteratorState a) = IteratorElement a
instance Iterable [a] where
type IterableElement [a] = a
instance Sequence [a] where
type SequenceElement [a] = a
getitem [] _ = Nothing
getitem [x] 0 = Just x
getitem (_:xs) i = getitem xs (i - 1)
type SequenceIteratorState a = IteratorState (a, Int)
instance Sequence a => Iterable (a, Int) where
type IterableElement (a, Int) = SequenceElement a
instance Sequence a => Iterator (SequenceIteratorState a) where
type IteratorElement (SequenceIteratorState a) = SequenceElement a
next (NextIterator (xs, idx)) = case getitem xs idx of
Nothing -> Nothing
Just x -> Just (NextIterator (xs, idx + 1), x)
data Cons a
= Nil
| a :> (Cons a)
instance Sequence (Cons a) where
type SequenceElement (Cons a) = a
getitem Nil _ = Nothing
getitem (x:>_) 0 = Just x
getitem (_:>xs) i = getitem xs (i - 1)
someSequenceElement :: Maybe String
someSequenceElement = snd <$> next (seqIter ("hello" :> Nil))
someList :: [String]
someList = ["a", "b", "c"]
someElement :: Maybe String
someElement = snd <$> next (iter (iter someList))
main :: IO ()
main = do
print (any someList)
print (all someList)
print (map length someList)
print (getitem someList 2)
print someElement
print someSequenceElement
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment