Skip to content

Instantly share code, notes, and snippets.

@abbradar
Last active June 12, 2016 14:19
Show Gist options
  • Save abbradar/a46337855d6c8abc05cc729388731167 to your computer and use it in GitHub Desktop.
Save abbradar/a46337855d6c8abc05cc729388731167 to your computer and use it in GitHub Desktop.
Example implementation of FromVector
{-# LANGUAGE PolyKinds, TypeFamilies, DataKinds, ScopedTypeVariables #-}
import GHC.TypeLits
import Data.Proxy
import Data.Vector (Vector)
import qualified Data.Vector as V
import Linear (V0(..), V1(..), V2(..), V3(..), V4(..))
import qualified Linear as L
import Linear.V (Dim, V)
import qualified Linear.V as LV
class FromVector t where
fromVector :: Vector a -> Maybe (t a)
instance Dim n => FromVector (V n) where
fromVector = LV.fromVector
instance FromVector V0 where
fromVector v | V.null v = Just V0
| otherwise = Nothing
instance FromVector V1 where
fromVector v = case V.toList v of
[a1] -> Just (V1 a1)
_ -> Nothing
instance FromVector V2 where
fromVector v = case V.toList v of
[a1, a2] -> Just (V2 a1 a2)
_ -> Nothing
instance FromVector V3 where
fromVector v = case V.toList v of
[a1, a2, a3] -> Just (V3 a1 a2 a3)
_ -> Nothing
instance FromVector V4 where
fromVector v = case V.toList v of
[a1, a2, a3, a4] -> Just (V4 a1 a2 a3 a4)
_ -> Nothing
matFromVector :: (FromVector m, FromVector t) => Vector (Vector a) -> Maybe (m (t a))
matFromVector v = sequence (fmap fromVector v) >>= fromVector
type family FixedSize (t :: k) :: Nat
type instance FixedSize V0 = 0
type instance FixedSize V1 = 1
type instance FixedSize V2 = 2
type instance FixedSize V3 = 3
type instance FixedSize V4 = 4
type instance FixedSize (V (n :: Nat)) = n
matFromVector' :: forall m t n a. (FromVector m, FromVector t, FixedSize t ~ n, KnownNat n) => Vector a -> Maybe (m (t a))
matFromVector' = matFromVector . V.fromList . splitBy (fromInteger $ natVal (Proxy :: Proxy n))
where splitBy n v
| V.null v = []
| otherwise = h : splitBy n t
where (h, t) = V.splitAt n v
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment