#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 708
#endif
module Data.DList.NonEmpty.Internal where
import Prelude ()
import Prelude.Compat hiding (concat, foldr, map, head, tail, replicate)
import Control.DeepSeq (NFData (..))
import Control.Monad
import Data.Function (on)
import Data.List.NonEmpty (NonEmpty (..))
import Data.Monoid (Endo (..))
import Data.Semigroup (Semigroup(..))
import Data.String (IsString(..))
import qualified Data.List as List
import qualified Data.List.NonEmpty as NE
import qualified Data.Foldable as F
import qualified Data.DList as DList
import Data.Functor.Apply (Apply (..))
import Data.Functor.Bind (Bind (..))
import Data.Functor.Alt (Alt (..))
import qualified Data.Semigroup.Foldable as SF
import qualified Data.Semigroup.Traversable as ST
#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
#endif
#endif
newtype NonEmptyDList a = NEDL { unNEDL :: [a] -> NonEmpty a }
fromNonEmpty :: NonEmpty a -> NonEmptyDList a
fromNonEmpty (x :| xs) = NEDL $ (x :|) . (xs ++)
toNonEmpty :: NonEmptyDList a -> NonEmpty a
toNonEmpty = ($[]) . unNEDL
toList :: NonEmptyDList a -> [a]
toList = NE.toList . toNonEmpty
toDList :: NonEmptyDList a -> DList.DList a
toDList = DList.fromList . toList
toEndo :: NonEmptyDList a -> Endo [a]
toEndo ne = Endo (NE.toList . unNEDL ne)
toEndo' :: NonEmptyDList a -> [a] -> [a]
toEndo' = appEndo . toEndo
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 708
#if __GLASGOW_HASKELL__ >= 710
pattern Cons :: a -> [a] -> NonEmptyDList a
#endif
pattern Cons x xs <- (toNonEmpty -> x :| xs)
#endif
apply :: NonEmptyDList a -> [a] -> NonEmpty a
apply = unNEDL
singleton :: a -> NonEmptyDList a
singleton = NEDL . (:|)
infixr `cons`
cons :: a -> NonEmptyDList a -> NonEmptyDList a
cons x xs = NEDL (NE.cons x . unNEDL xs)
infixl `snoc`
snoc :: NonEmptyDList a -> a -> NonEmptyDList a
snoc xs x = NEDL (unNEDL xs . (x:))
append :: NonEmptyDList a -> NonEmptyDList a -> NonEmptyDList a
append xs ys = NEDL (unNEDL xs . NE.toList . unNEDL ys)
concat1 :: NonEmpty (NonEmptyDList a) -> NonEmptyDList a
concat1 = sconcat
replicate :: Int -> a -> NonEmptyDList a
replicate n x = NEDL $ \xs -> let go m | m <= 1 = x :| xs
| otherwise = NE.cons x $ go (m1)
in go n
head :: NonEmptyDList a -> a
head = NE.head . toNonEmpty
tail :: NonEmptyDList a -> [a]
tail = NE.tail . toNonEmpty
unfoldr :: (b -> (a, Maybe b)) -> b -> NonEmptyDList a
unfoldr pf b = case pf b of
(a, Nothing) -> singleton a
(a, Just b') -> cons a (unfoldr pf b')
map :: (a -> b) -> NonEmptyDList a -> NonEmptyDList b
map f = fromNonEmpty . fmap f . toNonEmpty
instance Eq a => Eq (NonEmptyDList a) where
(==) = (==) `on` toList
instance Ord a => Ord (NonEmptyDList a) where
compare = compare `on` toList
instance Read a => Read (NonEmptyDList a) where
#ifdef __GLASGOW_HASKELL__
readPrec = parens $ prec 10 $ do
Ident "fromNonEmpty" <- lexP
dl <- readPrec
return (fromNonEmpty dl)
readListPrec = readListPrecDefault
#else
readsPrec p = readParen (p > 10) $ \r -> do
("fromNonEmpty", s) <- lex r
(dl, t) <- readsPrec 11 s
return (fromNonEmpty dl, t)
#endif
instance Show a => Show (NonEmptyDList a) where
showsPrec p dl = showParen (p > 10) $
showString "fromNonEmpty " . showsPrec 11 (toNonEmpty dl)
instance Functor NonEmptyDList where
fmap = map
instance Applicative NonEmptyDList where
pure = singleton
(<*>) = ap
instance Monad NonEmptyDList where
m >>= k
= concat1 . fmap k . toNonEmpty $ m
return = pure
instance Foldable NonEmptyDList where
fold = mconcat . toList
foldMap f = F.foldMap f . toList
foldr f x = List.foldr f x . toList
foldl f x = List.foldl f x . toList
foldr1 f = List.foldr1 f . toList
foldl1 f = List.foldl1 f . toList
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 706
foldl' f x = List.foldl' f x . toList
foldr' f x = F.foldr' f x . toList
#endif
instance Traversable NonEmptyDList where
traverse f = fmap fromNonEmpty . traverse f . toNonEmpty
sequenceA = fmap fromNonEmpty . sequenceA . toNonEmpty
instance NFData a => NFData (NonEmptyDList a) where
rnf = rnf . toNonEmpty
instance a ~ Char => IsString (NonEmptyDList a) where
fromString = fromNonEmpty . NE.fromList
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 708
instance IsList (NonEmptyDList a) where
type Item (NonEmptyDList a) = a
fromList = fromNonEmpty . NE.fromList
toList = toList
#endif
instance Semigroup (NonEmptyDList a) where
(<>) = append
instance Apply NonEmptyDList where (<.>) = (<*>)
instance Bind NonEmptyDList where (>>-) = (>>=)
instance SF.Foldable1 NonEmptyDList where
foldMap1 f = SF.foldMap1 f . toNonEmpty
#if MIN_VERSION_semigroupoids(5,2,1)
toNonEmpty = toNonEmpty
#endif
instance ST.Traversable1 NonEmptyDList where
traverse1 f = fmap fromNonEmpty . ST.traverse1 f . toNonEmpty
sequence1 = fmap fromNonEmpty . ST.sequence1 . toNonEmpty
instance Alt NonEmptyDList where
(<!>) = append