{-# OPTIONS_GHC -O2 #-}
{-# OPTIONS_HADDOCK prune #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 708
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE ViewPatterns #-}
#endif
module Data.DList
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 800
( DList(Nil, Cons)
#else
( DList
#endif
, fromList
, toList
, apply
, empty
, singleton
, cons
, snoc
, append
, concat
, replicate
, list
, head
, tail
, unfoldr
, foldr
, map
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 708 && __GLASGOW_HASKELL__ < 800
, pattern Nil
, pattern Cons
#endif
) where
import Prelude hiding (concat, foldr, map, head, tail, replicate)
import qualified Data.List as List
import Control.DeepSeq (NFData(..))
import Control.Monad as M
import Data.Function (on)
import Data.String (IsString(..))
import qualified Data.Foldable as F
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid
import Data.Foldable (Foldable)
import Control.Applicative(Applicative(..))
#endif
#if MIN_VERSION_base(4,9,0)
import Data.Semigroup (Semigroup(..))
#endif
#ifdef __GLASGOW_HASKELL__
import Text.Read (Lexeme(Ident), lexP, parens, prec, readPrec, readListPrec,
readListPrecDefault)
#if __GLASGOW_HASKELL__ >= 708
import GHC.Exts (IsList)
import qualified GHC.Exts (IsList(Item, fromList, toList))
#endif
#endif
import Control.Applicative(Alternative, (<|>))
import qualified Control.Applicative (empty)
newtype DList a = DL { unDL :: [a] -> [a] }
fromList :: [a] -> DList a
fromList = DL . (++)
{-# INLINE fromList #-}
toList :: DList a -> [a]
toList = ($[]) . unDL
{-# INLINE toList #-}
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 708
#if __GLASGOW_HASKELL__ >= 710
pattern Nil :: DList a
#endif
pattern Nil <- (toList -> [])
#if __GLASGOW_HASKELL__ >= 710
pattern Cons :: a -> [a] -> DList a
#endif
pattern Cons x xs <- (toList -> x:xs)
#endif
apply :: DList a -> [a] -> [a]
apply = unDL
empty :: DList a
empty = DL id
{-# INLINE empty #-}
singleton :: a -> DList a
singleton = DL . (:)
{-# INLINE singleton #-}
infixr `cons`
cons :: a -> DList a -> DList a
cons x xs = DL ((x:) . unDL xs)
{-# INLINE cons #-}
infixl `snoc`
snoc :: DList a -> a -> DList a
snoc xs x = DL (unDL xs . (x:))
{-# INLINE snoc #-}
append :: DList a -> DList a -> DList a
append xs ys = DL (unDL xs . unDL ys)
{-# INLINE append #-}
concat :: [DList a] -> DList a
concat = List.foldr append empty
{-# INLINE concat #-}
replicate :: Int -> a -> DList a
replicate n x = DL $ \xs -> let go m | m <= 0 = xs
| otherwise = x : go (m-1)
in go n
{-# INLINE replicate #-}
list :: b -> (a -> DList a -> b) -> DList a -> b
list nill consit dl =
case toList dl of
[] -> nill
(x : xs) -> consit x (fromList xs)
head :: DList a -> a
head = list (error "Data.DList.head: empty dlist") const
tail :: DList a -> DList a
tail = list (error "Data.DList.tail: empty dlist") (flip const)
unfoldr :: (b -> Maybe (a, b)) -> b -> DList a
unfoldr pf b =
case pf b of
Nothing -> empty
Just (a, b') -> cons a (unfoldr pf b')
foldr :: (a -> b -> b) -> b -> DList a -> b
foldr f b = List.foldr f b . toList
{-# INLINE foldr #-}
map :: (a -> b) -> DList a -> DList b
map f = foldr (cons . f) empty
{-# INLINE map #-}
instance Eq a => Eq (DList a) where
(==) = (==) `on` toList
instance Ord a => Ord (DList a) where
compare = compare `on` toList
instance Read a => Read (DList a) where
#ifdef __GLASGOW_HASKELL__
readPrec = parens $ prec 10 $ do
Ident "fromList" <- lexP
dl <- readPrec
return (fromList dl)
readListPrec = readListPrecDefault
#else
readsPrec p = readParen (p > 10) $ \r -> do
("fromList", s) <- lex r
(dl, t) <- reads s
return (fromList dl, t)
#endif
instance Show a => Show (DList a) where
showsPrec p dl = showParen (p > 10) $
showString "fromList " . shows (toList dl)
instance Monoid (DList a) where
mempty = empty
mappend = append
instance Functor DList where
fmap = map
{-# INLINE fmap #-}
instance Applicative DList where
pure = singleton
{-# INLINE pure #-}
(<*>) = ap
instance Alternative DList where
empty = empty
(<|>) = append
instance Monad DList where
m >>= k
= foldr (append . k) empty m
{-# INLINE (>>=) #-}
return = pure
{-# INLINE return #-}
fail _ = empty
{-# INLINE fail #-}
instance MonadPlus DList where
mzero = empty
mplus = append
instance Foldable DList where
fold = mconcat . toList
{-# INLINE fold #-}
foldMap f = F.foldMap f . toList
{-# INLINE foldMap #-}
foldr f x = List.foldr f x . toList
{-# INLINE foldr #-}
foldl f x = List.foldl f x . toList
{-# INLINE foldl #-}
foldr1 f = List.foldr1 f . toList
{-# INLINE foldr1 #-}
foldl1 f = List.foldl1 f . toList
{-# INLINE foldl1 #-}
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 706
foldl' f x = List.foldl' f x . toList
{-# INLINE foldl' #-}
foldr' f x = F.foldr' f x . toList
{-# INLINE foldr' #-}
#endif
instance NFData a => NFData (DList a) where
rnf = rnf . toList
{-# INLINE rnf #-}
instance a ~ Char => IsString (DList a) where
fromString = fromList
{-# INLINE fromString #-}
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 708
instance IsList (DList a) where
type Item (DList a) = a
fromList = fromList
{-# INLINE fromList #-}
toList = toList
{-# INLINE toList #-}
#endif
#if MIN_VERSION_base(4,9,0)
instance Semigroup (DList a) where
(<>) = append
{-# INLINE (<>) #-}
stimes n x
| n < 0 = error "Data.DList.stimes: negative multiplier"
| otherwise = rep n
where
rep 0 = empty
rep i = x <> rep (pred i)
#endif