{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
module Haskus.Utils.InfList
( InfList (..)
, toList
, repeat
, take
, replicate
)
where
import Prelude hiding (take,repeat,replicate)
data InfList a
= a :> InfList a
deriving (Functor,Foldable)
toList :: InfList a -> [a]
toList (a :> as) = a : toList as
take :: Word -> InfList a -> [a]
take 0 _ = []
take n (x :> xs) = x : take (n-1) xs
repeat :: a -> InfList a
repeat a = go
where
go = a :> go
replicate :: Word -> a -> InfList a -> InfList a
replicate 0 _ xs = xs
replicate n a xs = a :> replicate (n-1) a xs