
Hello, playing around with type classes, I came up with the idea to implement Matlab-like array slices by overloading the (!) - Operator. My first try goes
{-# LANGUAGE MultiParamTypeClasses , FunctionalDependencies , FlexibleContexts , FlexibleInstances #-}
import Data.Array.Unboxed hiding ((!)) import qualified Data.Array.Unboxed as AU
class Sliceable arrtype indtype resulttype | arrtype indtype -> resulttype where (!) :: arrtype -> indtype -> resulttype
instance (Ix i, IArray UArray e) => Sliceable (UArray i e) i e where (!) = (AU.!)
instance (Ix i, IArray UArray e) => Sliceable (UArray i e) [i] (UArray Int e) where (!) arr ilist = listArray (0,end_ind) [(AU.!) arr i | i <- ilist] where end_ind = length ilist - 1
In principle this seems to work, for instance ghci> let arr = listArray (0,99) [0..99] :: UArray Int Double ghci> arr ! (17::Int) 17.0 ghci> arr ! [13..15 :: Int] array (0,2) [(0,13.0),(1,14.0),(2,15.0)] However, the ugly type annotations (::Int) are necessary, otherwise I get an error message:
arr ! 17
No instance for (Sliceable (UArray Int Double) indtype0 resulttype0) arising from a use of `!' Possible fix: add an instance declaration for Sliceable (UArray Int Double) indtype resulttype0 in the expression: arr ! 17 whereas the type annotation is not necessary for the original Array.Unboxed - (!) :
(AU.!) arr 17 17.0
Could somebody please explain why the type annotation is necessary in my case? Is there a trick to circumvent this? Any hint would be welcome! Best regards Johannes
participants (1)
-
Johannes Engels