Skip to content

Commit 71964e8

Browse files
committed
Add Show1 and Read1 Vector instances
1 parent 098009c commit 71964e8

File tree

2 files changed

+18
-1
lines changed

2 files changed

+18
-1
lines changed

Data/Vector.hs

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -192,7 +192,7 @@ import Prelude hiding ( length, null,
192192
mapM, mapM_, sequence, sequence_ )
193193

194194
#if MIN_VERSION_base(4,9,0)
195-
import Data.Functor.Classes (Eq1 (..), Ord1 (..))
195+
import Data.Functor.Classes (Eq1 (..), Ord1 (..), Read1 (..), Show1 (..))
196196
#endif
197197

198198
import Data.Typeable ( Typeable )
@@ -232,6 +232,14 @@ instance Read a => Read (Vector a) where
232232
readPrec = G.readPrec
233233
readListPrec = readListPrecDefault
234234

235+
#if MIN_VERSION_base(4,9,0)
236+
instance Show1 Vector where
237+
liftShowsPrec = G.liftShowsPrec
238+
239+
instance Read1 Vector where
240+
liftReadsPrec = G.liftReadsPrec
241+
#endif
242+
235243
#if __GLASGOW_HASKELL__ >= 708
236244

237245
instance Exts.IsList (Vector a) where

Data/Vector/Generic.hs

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -162,6 +162,7 @@ module Data.Vector.Generic (
162162

163163
-- ** Show and Read
164164
showsPrec, readPrec,
165+
liftShowsPrec, liftReadsPrec,
165166

166167
-- ** @Data@ and @Typeable@
167168
gfoldl, dataCast, mkType
@@ -2157,13 +2158,21 @@ showsPrec :: (Vector v a, Show a) => Int -> v a -> ShowS
21572158
{-# INLINE showsPrec #-}
21582159
showsPrec _ = shows . toList
21592160

2161+
liftShowsPrec :: (Vector v a) => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> v a -> ShowS
2162+
{-# INLINE liftShowsPrec #-}
2163+
liftShowsPrec _ s _ = s . toList
2164+
21602165
-- | Generic definition of 'Text.Read.readPrec'
21612166
readPrec :: (Vector v a, Read a) => Read.ReadPrec (v a)
21622167
{-# INLINE readPrec #-}
21632168
readPrec = do
21642169
xs <- Read.readPrec
21652170
return (fromList xs)
21662171

2172+
-- | /Note:/ uses 'ReadS'
2173+
liftReadsPrec :: (Vector v a) => (Int -> Read.ReadS a) -> ReadS [a] -> Int -> Read.ReadS (v a)
2174+
liftReadsPrec _ r _ s = [ (fromList v, s') | (v, s') <- r s ]
2175+
21672176
-- Data and Typeable
21682177
-- -----------------
21692178

0 commit comments

Comments
 (0)