Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -9,3 +9,4 @@ cabal.sandbox.config
# cabal build outputs
dist
dist-newstyle
dist-mcabal
2 changes: 1 addition & 1 deletion Data/DList.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ module Data.DList
( -- * Difference List Type

-- CPP: GHC >= 8 for pattern synonyms allowed in the constructor
#if __GLASGOW_HASKELL__ >= 800
#if __GLASGOW_HASKELL__ >= 800 || __MHS__
DList (Nil, Cons),
#else
DList,
Expand Down
2 changes: 2 additions & 0 deletions Data/DList/DNonEmpty/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -460,6 +460,7 @@ instance a ~ Char => IsString (DNonEmpty a) where
{-# INLINE fromString #-}
fromString = fromList

#ifdef __GLASGOW_HASKELL__
instance Exts.IsList (DNonEmpty a) where
type Item (DNonEmpty a) = a

Expand All @@ -468,6 +469,7 @@ instance Exts.IsList (DNonEmpty a) where

{-# INLINE toList #-}
toList = toList
#endif

instance Semigroup.Semigroup (DNonEmpty a) where
{-# INLINE (<>) #-}
Expand Down
24 changes: 12 additions & 12 deletions Data/DList/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,8 @@ package depends on this module ('Data.DList.Internal'), we don't perform the
same check everywhere else.

-}
#if !defined(__GLASGOW_HASKELL__)
#error "Your compiler is not GHC. Let us know if dlist can be made to work on it."
#if !defined(__GLASGOW_HASKELL__) && !defined(__MHS__)
#error "Your compiler is not GHC or MicroHs. Let us know if dlist can be made to work on it."
#endif

-- For the IsList and IsString instances
Expand Down Expand Up @@ -64,9 +64,9 @@ import qualified Control.Applicative as Applicative
import Control.DeepSeq (NFData (..))
import qualified Control.Monad as Monad
-- CPP: base >= 4.9 for MonadFail
-- CPP: base >= 4.13 for MonadFail exported from Control.Monad
-- CPP: base >= 4.13 for MonadFail exported from Prelude
#if MIN_VERSION_base(4,9,0) && !MIN_VERSION_base(4,13,0)
import qualified Control.Monad.Fail as Monad
import Control.Monad.Fail (MonadFail (..))
#endif
import qualified Data.Foldable as Foldable
import Data.Function (on)
Expand Down Expand Up @@ -159,10 +159,10 @@ construction.
toList :: DList a -> [a]
toList = ($ []) . unsafeApplyDList

-- CPP: GHC >= 7.8 for pattern synonyms
#if __GLASGOW_HASKELL__ >= 708
-- CPP: GHC >= 7.8 or MicroHs for pattern synonyms
#if __GLASGOW_HASKELL__ >= 708 || __MHS__

-- CPP: GHC >= 7.10 for pattern synonym signatures
-- CPP: GHC >= 7.10 or MicroHs for pattern synonym signatures

{- ORMOLU_DISABLE -}
{-|
Expand All @@ -172,7 +172,7 @@ A unidirectional pattern synonym for 'empty'. This is implemented with 'toList'.
-}
{- ORMOLU_ENABLE -}

#if __GLASGOW_HASKELL__ >= 710
#if __GLASGOW_HASKELL__ >= 710 || __MHS__
pattern Nil :: DList a
#endif
pattern Nil <- (toList -> [])
Expand All @@ -185,7 +185,7 @@ A unidirectional pattern synonym for 'cons'. This is implemented with 'toList'.
-}
{- ORMOLU_ENABLE -}

#if __GLASGOW_HASKELL__ >= 710
#if __GLASGOW_HASKELL__ >= 710 || __MHS__
pattern Cons :: a -> [a] -> DList a
#endif
pattern Cons x xs <- (toList -> x : xs)
Expand Down Expand Up @@ -574,7 +574,7 @@ instance Monad DList where

-- CPP: base >= 4.9 for MonadFail
#if MIN_VERSION_base(4,9,0)
instance Monad.MonadFail DList where
instance MonadFail DList where
{-# INLINE fail #-}
fail _ = empty
#endif
Expand Down Expand Up @@ -605,8 +605,8 @@ instance Foldable.Foldable DList where
{-# INLINE foldl1 #-}
foldl1 f = List.foldl1 f . toList

-- CPP: GHC >= 7.6 for foldl', foldr' in Foldable
#if __GLASGOW_HASKELL__ >= 706
-- CPP: base >= 4.6 for foldl', foldr' in Foldable
#if MIN_VERSION_base(4,6,0)
{-# INLINE foldl' #-}
foldl' f x = List.foldl' f x . toList

Expand Down
4 changes: 2 additions & 2 deletions dlist.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ maintainer: Sean Leather <[email protected]>
copyright: 2006-2009 Don Stewart, 2013-2020 Sean Leather, 2017-2020 Oleg Grenrus, contributors
homepage: https://github.com/spl/dlist
bug-reports: https://github.com/spl/dlist/issues
extra-source-files: readme.md,
extra-source-files: readme.md
changelog.md
tests/ImportUnsafe.hs
build-type: Simple
Expand Down Expand Up @@ -51,7 +51,7 @@ library
exposed-modules: Data.DList
Data.DList.Unsafe
other-modules: Data.DList.Internal
if impl(ghc >= 8.0)
if impl(ghc >= 8.0) || impl(mhs)
exposed-modules: Data.DList.DNonEmpty
other-modules: Data.DList.DNonEmpty.Internal
default-language: Haskell2010
Expand Down