Skip to content

Commit c0dd6e4

Browse files
authored
Merge pull request #110 from silkapp/semigroups
Add Semigroup instances matching all Monoids.
2 parents c2e751c + 1609263 commit c0dd6e4

File tree

6 files changed

+50
-18
lines changed

6 files changed

+50
-18
lines changed

Data/Vector.hs

Lines changed: 11 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -185,9 +185,10 @@ import Prelude hiding ( length, null,
185185
enumFromTo, enumFromThenTo,
186186
mapM, mapM_, sequence, sequence_ )
187187

188-
import Data.Typeable ( Typeable )
189-
import Data.Data ( Data(..) )
190-
import Text.Read ( Read(..), readListPrecDefault )
188+
import Data.Typeable ( Typeable )
189+
import Data.Data ( Data(..) )
190+
import Text.Read ( Read(..), readListPrecDefault )
191+
import Data.Semigroup ( Semigroup(..) )
191192

192193
import qualified Control.Applicative as Applicative
193194
import qualified Data.Foldable as Foldable
@@ -286,6 +287,13 @@ instance Ord a => Ord (Vector a) where
286287
{-# INLINE (>=) #-}
287288
xs >= ys = Bundle.cmp (G.stream xs) (G.stream ys) /= LT
288289

290+
instance Semigroup (Vector a) where
291+
{-# INLINE (<>) #-}
292+
(<>) = (++)
293+
294+
{-# INLINE sconcat #-}
295+
sconcat = G.concatNE
296+
289297
instance Monoid (Vector a) where
290298
{-# INLINE mempty #-}
291299
mempty = empty
@@ -1597,4 +1605,3 @@ unsafeCopy = G.unsafeCopy
15971605
copy :: PrimMonad m => MVector (PrimState m) a -> Vector a -> m ()
15981606
{-# INLINE copy #-}
15991607
copy = G.copy
1600-

Data/Vector/Generic.hs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ module Data.Vector.Generic (
4949
enumFromN, enumFromStepN, enumFromTo, enumFromThenTo,
5050

5151
-- ** Concatenation
52-
cons, snoc, (++), concat,
52+
cons, snoc, (++), concat, concatNE,
5353

5454
-- ** Restricting memory usage
5555
force,
@@ -196,6 +196,7 @@ import Prelude hiding ( length, null,
196196
showsPrec )
197197

198198
import qualified Text.Read as Read
199+
import qualified Data.List.NonEmpty as NonEmpty
199200

200201
#if __GLASGOW_HASKELL__ >= 707
201202
import Data.Typeable ( Typeable, gcast1 )
@@ -687,6 +688,10 @@ concat vs = unstream (Bundle.flatten mk step (Exact n) (Bundle.fromList vs))
687688
k `seq` (v,0,k)
688689
-}
689690

691+
-- | /O(n)/ Concatenate all vectors in the non-empty list
692+
concatNE :: Vector v a => NonEmpty.NonEmpty (v a) -> v a
693+
concatNE = concat . NonEmpty.toList
694+
690695
-- Monadic initialisation
691696
-- ----------------------
692697

@@ -2119,4 +2124,3 @@ dataCast :: (Vector v a, Data a, Typeable1 v, Typeable1 t)
21192124
=> (forall d. Data d => c (t d)) -> Maybe (c (v a))
21202125
{-# INLINE dataCast #-}
21212126
dataCast f = gcast1 f
2122-

Data/Vector/Primitive.hs

Lines changed: 11 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -160,9 +160,10 @@ import Prelude hiding ( length, null,
160160
enumFromTo, enumFromThenTo,
161161
mapM, mapM_ )
162162

163-
import Data.Typeable ( Typeable )
164-
import Data.Data ( Data(..) )
165-
import Text.Read ( Read(..), readListPrecDefault )
163+
import Data.Typeable ( Typeable )
164+
import Data.Data ( Data(..) )
165+
import Text.Read ( Read(..), readListPrecDefault )
166+
import Data.Semigroup ( Semigroup(..) )
166167

167168
#if !MIN_VERSION_base(4,8,0)
168169
import Data.Monoid ( Monoid(..) )
@@ -250,6 +251,13 @@ instance (Prim a, Ord a) => Ord (Vector a) where
250251
{-# INLINE (>=) #-}
251252
xs >= ys = Bundle.cmp (G.stream xs) (G.stream ys) /= LT
252253

254+
instance Prim a => Semigroup (Vector a) where
255+
{-# INLINE (<>) #-}
256+
(<>) = (++)
257+
258+
{-# INLINE sconcat #-}
259+
sconcat = G.concatNE
260+
253261
instance Prim a => Monoid (Vector a) where
254262
{-# INLINE mempty #-}
255263
mempty = empty
@@ -1338,5 +1346,3 @@ unsafeCopy = G.unsafeCopy
13381346
copy :: (Prim a, PrimMonad m) => MVector (PrimState m) a -> Vector a -> m ()
13391347
{-# INLINE copy #-}
13401348
copy = G.copy
1341-
1342-

Data/Vector/Storable.hs

Lines changed: 11 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -165,9 +165,10 @@ import Prelude hiding ( length, null,
165165
enumFromTo, enumFromThenTo,
166166
mapM, mapM_ )
167167

168-
import Data.Typeable ( Typeable )
169-
import Data.Data ( Data(..) )
170-
import Text.Read ( Read(..), readListPrecDefault )
168+
import Data.Typeable ( Typeable )
169+
import Data.Data ( Data(..) )
170+
import Text.Read ( Read(..), readListPrecDefault )
171+
import Data.Semigroup ( Semigroup(..) )
171172

172173
#if !MIN_VERSION_base(4,8,0)
173174
import Data.Monoid ( Monoid(..) )
@@ -259,6 +260,13 @@ instance (Storable a, Ord a) => Ord (Vector a) where
259260
{-# INLINE (>=) #-}
260261
xs >= ys = Bundle.cmp (G.stream xs) (G.stream ys) /= LT
261262

263+
instance Storable a => Semigroup (Vector a) where
264+
{-# INLINE (<>) #-}
265+
(<>) = (++)
266+
267+
{-# INLINE sconcat #-}
268+
sconcat = G.concatNE
269+
262270
instance Storable a => Monoid (Vector a) where
263271
{-# INLINE mempty #-}
264272
mempty = empty
@@ -1434,5 +1442,3 @@ unsafeToForeignPtr0 (Vector n fp) = (fp, n)
14341442
unsafeWith :: Storable a => Vector a -> (Ptr a -> IO b) -> IO b
14351443
{-# INLINE unsafeWith #-}
14361444
unsafeWith (Vector _ fp) = withForeignPtr fp
1437-
1438-

Data/Vector/Unboxed.hs

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -184,7 +184,8 @@ import Prelude hiding ( length, null,
184184
enumFromTo, enumFromThenTo,
185185
mapM, mapM_ )
186186

187-
import Text.Read ( Read(..), readListPrecDefault )
187+
import Text.Read ( Read(..), readListPrecDefault )
188+
import Data.Semigroup ( Semigroup(..) )
188189

189190
#if !MIN_VERSION_base(4,8,0)
190191
import Data.Monoid ( Monoid(..) )
@@ -222,6 +223,13 @@ instance (Unbox a, Ord a) => Ord (Vector a) where
222223
{-# INLINE (>=) #-}
223224
xs >= ys = Bundle.cmp (G.stream xs) (G.stream ys) /= LT
224225

226+
instance Unbox a => Semigroup (Vector a) where
227+
{-# INLINE (<>) #-}
228+
(<>) = (++)
229+
230+
{-# INLINE sconcat #-}
231+
sconcat = G.concatNE
232+
225233
instance Unbox a => Monoid (Vector a) where
226234
{-# INLINE mempty #-}
227235
mempty = empty
@@ -1433,4 +1441,3 @@ copy = G.copy
14331441

14341442
#define DEFINE_IMMUTABLE
14351443
#include "unbox-tuple-instances"
1436-

vector.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -142,6 +142,8 @@ Library
142142
, primitive >= 0.5.0.1 && < 0.7
143143
, ghc-prim >= 0.2 && < 0.6
144144
, deepseq >= 1.1 && < 1.5
145+
if !impl(ghc > 8.0)
146+
Build-Depends: semigroups >= 0.18 && < 0.19
145147

146148
Ghc-Options: -O2 -Wall -fno-warn-orphans
147149

0 commit comments

Comments
 (0)