module StrictList where
import StrictList.Prelude hiding (take, drop, takeWhile, dropWhile, reverse)
data List a = Cons !a !(List a) | Nil deriving
(Eq, Ord, Show, Read, Generic, Generic1, Data, Typeable)
instance IsList (List a) where
type Item (List a) = a
fromList = reverse . fromListReversed
toList = foldr (:) []
instance Semigroup (List a) where
(<>) a b = case b of
Nil -> a
_ -> prependReversed (reverse a) b
instance Monoid (List a) where
mempty = Nil
mappend = (<>)
instance Functor List where
fmap f = reverse . mapReversed f
instance Foldable List where
foldr step init = let
loop = \ case
Cons head tail -> step head (loop tail)
_ -> init
in loop
foldl' step init = let
loop !acc = \ case
Cons head tail -> loop (step acc head) tail
_ -> acc
in loop init
instance Traversable List where
sequenceA = foldr (liftA2 Cons) (pure Nil)
instance Apply List where
(<.>) fList aList = apReversed (reverse fList) (reverse aList)
instance Applicative List where
pure a = Cons a Nil
(<*>) = (<.>)
instance Alt List where
(<!>) = mappend
instance Plus List where
zero = mempty
instance Alternative List where
empty = zero
(<|>) = (<!>)
instance Bind List where
(>>-) ma amb = reverse (explodeReversed amb ma)
join = reverse . joinReversed
instance Monad List where
return = pure
(>>=) = (>>-)
instance MonadPlus List where
mzero = empty
mplus = (<|>)
reverse :: List a -> List a
reverse = foldl' (flip Cons) Nil
take :: Int -> List a -> List a
take amount = reverse . takeReversed amount
takeReversed :: Int -> List a -> List a
takeReversed = let
loop !output !amount = if amount > 0
then \ case
Cons head tail -> loop (Cons head output) (pred amount) tail
_ -> output
else const output
in loop Nil
drop :: Int -> List a -> List a
drop amount = if amount > 0
then \ case
Cons _ tail -> drop (pred amount) tail
_ -> Nil
else id
filter :: (a -> Bool) -> List a -> List a
filter predicate = reverse . filterReversed predicate
filterReversed :: (a -> Bool) -> List a -> List a
filterReversed predicate = let
loop !newList = \ case
Cons head tail -> if predicate head
then loop (Cons head newList) tail
else loop newList tail
Nil -> newList
in loop Nil
takeWhile :: (a -> Bool) -> List a -> List a
takeWhile predicate = reverse . takeWhileReversed predicate
takeWhileReversed :: (a -> Bool) -> List a -> List a
takeWhileReversed predicate = let
loop !newList = \ case
Cons head tail -> if predicate head
then loop (Cons head newList) tail
else newList
_ -> newList
in loop Nil
dropWhile :: (a -> Bool) -> List a -> List a
dropWhile predicate = \ case
Cons head tail -> if predicate head
then dropWhile predicate tail
else Cons head tail
Nil -> Nil
span :: (a -> Bool) -> List a -> (List a, List a)
span predicate = first reverse . spanReversed predicate
spanReversed :: (a -> Bool) -> List a -> (List a, List a)
spanReversed predicate = let
buildPrefix !prefix = \ case
Cons head tail -> if predicate head
then buildPrefix (Cons head prefix) tail
else (prefix, Cons head tail)
_ -> (prefix, Nil)
in buildPrefix Nil
break :: (a -> Bool) -> List a -> (List a, List a)
break predicate = first reverse . breakReversed predicate
breakReversed :: (a -> Bool) -> List a -> (List a, List a)
breakReversed predicate = let
buildPrefix !prefix = \ case
Cons head tail -> if predicate head
then (prefix, Cons head tail)
else buildPrefix (Cons head prefix) tail
_ -> (prefix, Nil)
in buildPrefix Nil
takeWhileFromEnding :: (a -> Bool) -> List a -> List a
takeWhileFromEnding predicate = foldl'
(\ newList a -> if predicate a
then Cons a newList
else Nil)
Nil
dropWhileFromEnding :: (a -> Bool) -> List a -> List a
dropWhileFromEnding predicate = let
loop confirmed unconfirmed = \ case
Cons head tail -> if predicate head
then loop confirmed (Cons head unconfirmed) tail
else let
!newConfirmed = Cons head unconfirmed
in loop newConfirmed newConfirmed tail
Nil -> confirmed
in loop Nil Nil
spanFromEnding :: (a -> Bool) -> List a -> (List a, List a)
spanFromEnding predicate = let
loop !confirmedPrefix !unconfirmedPrefix !suffix = \ case
Cons head tail -> if predicate head
then loop confirmedPrefix (Cons head unconfirmedPrefix) (Cons head suffix) tail
else let
!prefix = Cons head unconfirmedPrefix
in loop prefix prefix Nil tail
Nil -> (suffix, confirmedPrefix)
in loop Nil Nil Nil
uncons :: List a -> Maybe (a, List a)
uncons = \ case
Cons head tail -> Just (head, tail)
_ -> Nothing
head :: List a -> Maybe a
head = \ case
Cons head _ -> Just head
_ -> Nothing
last :: List a -> Maybe a
last = let
loop !previous = \ case
Cons head tail -> loop (Just head) tail
_ -> previous
in loop Nothing
tail :: List a -> List a
tail = \ case
Cons _ tail -> tail
Nil -> Nil
init :: List a -> List a
init = reverse . initReversed
initReversed :: List a -> List a
initReversed = let
loop !confirmed !unconfirmed = \ case
Cons head tail -> loop unconfirmed (Cons head unconfirmed) tail
_ -> confirmed
in loop Nil Nil
apZipping :: List (a -> b) -> List a -> List b
apZipping left right = apZippingReversed (reverse left) (reverse right)
apZippingReversed :: List (a -> b) -> List a -> List b
apZippingReversed = let
loop bList = \ case
Cons f fTail -> \ case
Cons a aTail -> loop (Cons (f a) bList) fTail aTail
_ -> bList
_ -> const bList
in loop Nil
fromListReversed :: [a] -> List a
fromListReversed = foldl' (flip Cons) Nil
prependReversed :: List a -> List a -> List a
prependReversed = \ case
Cons head tail -> prependReversed tail . Cons head
Nil -> id
mapReversed :: (a -> b) -> List a -> List b
mapReversed f = let
loop !newList = \ case
Cons head tail -> loop (Cons (f head) newList) tail
_ -> newList
in loop Nil
apReversed :: List (a -> b) -> List a -> List b
apReversed fList aList = foldl' (\ z f -> foldl' (\ z a -> Cons (f a) z) z aList) Nil fList
explodeReversed :: (a -> List b) -> List a -> List b
explodeReversed amb = foldl' (\ z -> foldl' (flip Cons) z . amb) Nil
joinReversed :: List (List a) -> List a
joinReversed = foldl' (foldl' (flip Cons)) Nil