@@ -1335,11 +1335,10 @@ postscanr f z xs = init (scanr f z xs)
13351335mapAccumL :: (acc -> x -> (acc ,y )) -> acc -> Vec n x -> (acc ,Vec n y )
13361336mapAccumL f acc xs = (acc',ys)
13371337 where
1338- accs = acc `Cons ` accs'
1339- ws = zipWith (flip f) xs (init accs)
1340- accs' = map fst ws
1341- ys = map snd ws
1342- acc' = last accs
1338+ accs = acc `Cons ` accs'
1339+ ws = zipWith (flip f) xs (init accs)
1340+ (accs', ys) = unzip ws
1341+ acc' = last accs
13431342{-# INLINE mapAccumL #-}
13441343
13451344-- | The 'mapAccumR' function behaves like a combination of 'map' and 'foldr';
@@ -1356,11 +1355,10 @@ mapAccumL f acc xs = (acc',ys)
13561355mapAccumR :: (acc -> x -> (acc ,y )) -> acc -> Vec n x -> (acc , Vec n y )
13571356mapAccumR f acc xs = (acc',ys)
13581357 where
1359- accs = accs' :< acc
1360- ws = zipWith (flip f) xs (tail accs)
1361- accs' = map fst ws
1362- ys = map snd ws
1363- acc' = head accs
1358+ accs = accs' :< acc
1359+ ws = zipWith (flip f) xs (tail accs)
1360+ (accs', ys) = unzip ws
1361+ acc' = head accs
13641362{-# INLINE mapAccumR #-}
13651363
13661364-- | 'zip' takes two vectors and returns a vector of corresponding pairs.
@@ -1424,7 +1422,15 @@ zip7 = zipWith7 (,,,,,,)
14241422-- >>> unzip ((1,4):>(2,3):>(3,2):>(4,1):>Nil)
14251423-- (1 :> 2 :> 3 :> 4 :> Nil,4 :> 3 :> 2 :> 1 :> Nil)
14261424unzip :: Vec n (a ,b ) -> (Vec n a , Vec n b )
1427- unzip xs = (map fst xs, map snd xs)
1425+ unzip xs
1426+ | clashSimulation = unzipSim xs
1427+ | otherwise = (map fst xs, map snd xs)
1428+ where
1429+ unzipSim :: Vec m (a ,b ) -> (Vec m a , Vec m b )
1430+ unzipSim Nil = (Nil , Nil )
1431+ unzipSim (~ (a,b) `Cons ` rest) =
1432+ let (as, bs) = unzipSim rest
1433+ in (a `Cons ` as, b `Cons ` bs)
14281434{-# INLINE unzip #-}
14291435
14301436-- | 'unzip3' transforms a vector of triplets into a vector of first components,
@@ -1433,60 +1439,100 @@ unzip xs = (map fst xs, map snd xs)
14331439-- >>> unzip3 ((1,4,5):>(2,3,6):>(3,2,7):>(4,1,8):>Nil)
14341440-- (1 :> 2 :> 3 :> 4 :> Nil,4 :> 3 :> 2 :> 1 :> Nil,5 :> 6 :> 7 :> 8 :> Nil)
14351441unzip3 :: Vec n (a ,b ,c ) -> (Vec n a , Vec n b , Vec n c )
1436- unzip3 xs = ( map (\ (x,_,_) -> x) xs
1437- , map (\ (_,y,_) -> y) xs
1438- , map (\ (_,_,z) -> z) xs
1439- )
1442+ unzip3 xs
1443+ | clashSimulation = unzip3Sim xs
1444+ | otherwise = ( map (\ (x,_,_) -> x) xs
1445+ , map (\ (_,y,_) -> y) xs
1446+ , map (\ (_,_,z) -> z) xs
1447+ )
1448+ where
1449+ unzip3Sim :: Vec m (a ,b ,c ) -> (Vec m a , Vec m b , Vec m c )
1450+ unzip3Sim Nil = (Nil , Nil , Nil )
1451+ unzip3Sim (~ (a,b,c) `Cons ` rest) =
1452+ let (as, bs, cs) = unzip3Sim rest
1453+ in (a `Cons ` as, b `Cons ` bs, c `Cons ` cs)
14401454{-# INLINE unzip3 #-}
14411455
14421456-- | 'unzip4' takes a vector of quadruples and returns four vectors, analogous
14431457-- to 'unzip'.
14441458unzip4 :: Vec n (a ,b ,c ,d ) -> (Vec n a , Vec n b , Vec n c , Vec n d )
1445- unzip4 xs = ( map (\ (w,_,_,_) -> w) xs
1446- , map (\ (_,x,_,_) -> x) xs
1447- , map (\ (_,_,y,_) -> y) xs
1448- , map (\ (_,_,_,z) -> z) xs
1449- )
1459+ unzip4 xs
1460+ | clashSimulation = unzip4Sim xs
1461+ | otherwise = ( map (\ (w,_,_,_) -> w) xs
1462+ , map (\ (_,x,_,_) -> x) xs
1463+ , map (\ (_,_,y,_) -> y) xs
1464+ , map (\ (_,_,_,z) -> z) xs
1465+ )
1466+ where
1467+ unzip4Sim :: Vec m (a ,b ,c ,d ) -> (Vec m a , Vec m b , Vec m c , Vec m d )
1468+ unzip4Sim Nil = (Nil , Nil , Nil , Nil )
1469+ unzip4Sim (~ (a,b,c,d) `Cons ` rest) =
1470+ let (as, bs, cs, ds) = unzip4Sim rest
1471+ in (a `Cons ` as, b `Cons ` bs, c `Cons ` cs, d `Cons ` ds)
14501472{-# INLINE unzip4 #-}
14511473
14521474-- | 'unzip5' takes a vector of five-tuples and returns five vectors, analogous
14531475-- to 'unzip'.
14541476unzip5 :: Vec n (a ,b ,c ,d ,e ) -> (Vec n a , Vec n b , Vec n c , Vec n d , Vec n e )
1455- unzip5 xs = ( map (\ (v,_,_,_,_) -> v) xs
1456- , map (\ (_,w,_,_,_) -> w) xs
1457- , map (\ (_,_,x,_,_) -> x) xs
1458- , map (\ (_,_,_,y,_) -> y) xs
1459- , map (\ (_,_,_,_,z) -> z) xs
1460- )
1477+ unzip5 xs
1478+ | clashSimulation = unzip5Sim xs
1479+ | otherwise = ( map (\ (v,_,_,_,_) -> v) xs
1480+ , map (\ (_,w,_,_,_) -> w) xs
1481+ , map (\ (_,_,x,_,_) -> x) xs
1482+ , map (\ (_,_,_,y,_) -> y) xs
1483+ , map (\ (_,_,_,_,z) -> z) xs
1484+ )
1485+ where
1486+ unzip5Sim :: Vec m (a ,b ,c ,d ,e ) -> (Vec m a , Vec m b , Vec m c , Vec m d , Vec m e )
1487+ unzip5Sim Nil = (Nil , Nil , Nil , Nil , Nil )
1488+ unzip5Sim (~ (a,b,c,d,e) `Cons ` rest) =
1489+ let (as, bs, cs, ds, es) = unzip5Sim rest
1490+ in (a `Cons ` as, b `Cons ` bs, c `Cons ` cs, d `Cons ` ds, e `Cons ` es)
14611491{-# INLINE unzip5 #-}
14621492
14631493-- | 'unzip6' takes a vector of six-tuples and returns six vectors, analogous
14641494-- to 'unzip'.
14651495unzip6
14661496 :: Vec n (a ,b ,c ,d ,e ,f )
14671497 -> (Vec n a , Vec n b , Vec n c , Vec n d , Vec n e , Vec n f )
1468- unzip6 xs = ( map (\ (u,_,_,_,_,_) -> u) xs
1469- , map (\ (_,v,_,_,_,_) -> v) xs
1470- , map (\ (_,_,w,_,_,_) -> w) xs
1471- , map (\ (_,_,_,x,_,_) -> x) xs
1472- , map (\ (_,_,_,_,y,_) -> y) xs
1473- , map (\ (_,_,_,_,_,z) -> z) xs
1474- )
1498+ unzip6 xs
1499+ | clashSimulation = unzip6Sim xs
1500+ | otherwise = ( map (\ (u,_,_,_,_,_) -> u) xs
1501+ , map (\ (_,v,_,_,_,_) -> v) xs
1502+ , map (\ (_,_,w,_,_,_) -> w) xs
1503+ , map (\ (_,_,_,x,_,_) -> x) xs
1504+ , map (\ (_,_,_,_,y,_) -> y) xs
1505+ , map (\ (_,_,_,_,_,z) -> z) xs
1506+ )
1507+ where
1508+ unzip6Sim :: Vec m (a ,b ,c ,d ,e ,f ) -> (Vec m a , Vec m b , Vec m c , Vec m d , Vec m e , Vec m f )
1509+ unzip6Sim Nil = (Nil , Nil , Nil , Nil , Nil , Nil )
1510+ unzip6Sim (~ (a,b,c,d,e,f) `Cons ` rest) =
1511+ let (as, bs, cs, ds, es, fs) = unzip6Sim rest
1512+ in (a `Cons ` as, b `Cons ` bs, c `Cons ` cs, d `Cons ` ds, e `Cons ` es, f `Cons ` fs)
14751513{-# INLINE unzip6 #-}
14761514
14771515-- | 'unzip7' takes a vector of seven-tuples and returns seven vectors, analogous
14781516-- to 'unzip'.
14791517unzip7
14801518 :: Vec n (a ,b ,c ,d ,e ,f ,g )
14811519 -> (Vec n a , Vec n b , Vec n c , Vec n d , Vec n e , Vec n f , Vec n g )
1482- unzip7 xs = ( map (\ (t,_,_,_,_,_,_) -> t) xs
1483- , map (\ (_,u,_,_,_,_,_) -> u) xs
1484- , map (\ (_,_,v,_,_,_,_) -> v) xs
1485- , map (\ (_,_,_,w,_,_,_) -> w) xs
1486- , map (\ (_,_,_,_,x,_,_) -> x) xs
1487- , map (\ (_,_,_,_,_,y,_) -> y) xs
1488- , map (\ (_,_,_,_,_,_,z) -> z) xs
1489- )
1520+ unzip7 xs
1521+ | clashSimulation = unzip7Sim xs
1522+ | otherwise = ( map (\ (t,_,_,_,_,_,_) -> t) xs
1523+ , map (\ (_,u,_,_,_,_,_) -> u) xs
1524+ , map (\ (_,_,v,_,_,_,_) -> v) xs
1525+ , map (\ (_,_,_,w,_,_,_) -> w) xs
1526+ , map (\ (_,_,_,_,x,_,_) -> x) xs
1527+ , map (\ (_,_,_,_,_,y,_) -> y) xs
1528+ , map (\ (_,_,_,_,_,_,z) -> z) xs
1529+ )
1530+ where
1531+ unzip7Sim :: Vec m (a ,b ,c ,d ,e ,f ,g ) -> (Vec m a , Vec m b , Vec m c , Vec m d , Vec m e , Vec m f , Vec m g )
1532+ unzip7Sim Nil = (Nil , Nil , Nil , Nil , Nil , Nil , Nil )
1533+ unzip7Sim (~ (a,b,c,d,e,f,g) `Cons ` rest) =
1534+ let (as, bs, cs, ds, es, fs, gs) = unzip7Sim rest
1535+ in (a `Cons ` as, b `Cons ` bs, c `Cons ` cs, d `Cons ` ds, e `Cons ` es, f `Cons ` fs, g `Cons ` gs)
14901536{-# INLINE unzip7 #-}
14911537
14921538
0 commit comments