Skip to content

Commit

Permalink
Add Stream instances for L and LN
Browse files Browse the repository at this point in the history
  • Loading branch information
lehins committed Sep 7, 2019
1 parent 9b925c8 commit 22c3776
Show file tree
Hide file tree
Showing 3 changed files with 41 additions and 1 deletion.
3 changes: 2 additions & 1 deletion massiv-test/massiv-test.cabal
Expand Up @@ -51,9 +51,10 @@ test-suite tests
main-is: Main.hs
other-modules: Spec
, Test.Massiv.Core.IndexSpec
, Test.Massiv.Core.ListSpec
, Test.Massiv.Core.SchedulerSpec
, Test.Massiv.Array.MutableSpec
, Test.Massiv.Array.Delayed.StreamSpec
, Test.Massiv.Array.MutableSpec
-- TODO: Below should be moved to Test.Massiv.Array
, Data.Massiv.Array.Delayed.InterleavedSpec
, Data.Massiv.Array.Delayed.PushSpec
Expand Down
21 changes: 21 additions & 0 deletions massiv-test/tests/Test/Massiv/Core/ListSpec.hs
@@ -0,0 +1,21 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Test.Massiv.Core.ListSpec (spec) where

import Data.Massiv.Array
import Test.Massiv.Core
import Test.Massiv.Array.Delayed


spec :: Spec
spec = do
describe "L" $
it "toStream" $ property (prop_toStreamIsList @L @Int)
describe "LN" $
it "toStream" $ property (prop_toStreamIsList @LN @Int)
18 changes: 18 additions & 0 deletions massiv/src/Data/Massiv/Core/List.hs
Expand Up @@ -32,6 +32,7 @@ import Control.Scheduler
import Data.Coerce
import Data.Foldable (foldr')
import qualified Data.List as L
import qualified Data.Massiv.Array.Manifest.Vector.Stream as S
import Data.Massiv.Core.Common
import Data.Typeable
import GHC.Exts
Expand All @@ -48,6 +49,14 @@ type instance NestedStruct LN ix e = [ListItem ix e]
newtype instance Array LN ix e = List { unList :: [Elt LN ix e] }


instance Construct LN Ix1 e where
setComp _ = id
{-# INLINE setComp #-}
makeArray _ (Sz n) f = coerce (fmap f [0 .. n - 1])
{-# INLINE makeArray #-}
makeArrayLinear _ (Sz n) f = coerce (fmap f [0 .. n - 1])
{-# INLINE makeArrayLinear #-}

instance {-# OVERLAPPING #-} Nested LN Ix1 e where
fromNested = coerce
{-# INLINE fromNested #-}
Expand Down Expand Up @@ -368,3 +377,12 @@ instance Ragged L ix e => OuterSlice L ix e where
Just (x, _) | n == i -> x
Just (_, xs) -> go (n + 1) xs
{-# INLINE unsafeOuterSlice #-}


instance Stream LN Ix1 e where
toStream = S.fromList . coerce
{-# INLINE toStream #-}

instance Ragged L ix e => Stream L ix e where
toStream = S.fromList . coerce . lData . flattenRagged
{-# INLINE toStream #-}

0 comments on commit 22c3776

Please sign in to comment.