
Hello, So, I would like to make an UArray of LogFloat. They are a newtype of Double, but the type system can't see trough newtypes. So I wonder if it is acceptable to exploit the fact that the internal representation of newtypes don't change to use some safe unsafeCoerces and create an instance of IArray for UArray of LogFloat. I've looked at the core of the code below and it seems sane, and -Wall only warn about the orphan instance, so I would also like to ask to include this instance in logfloat package itself (I've sent a copy of this message to LogFloat's maintainer). {-# LANGUAGE MultiParamTypeClasses #-} import Data.Array.Base import Data.Array.Unboxed (UArray) import Data.Number.LogFloat import Unsafe.Coerce -- For testing below import Data.Array.Unboxed as U import Test.QuickCheck {-# INLINE from #-} from :: UArray a LogFloat -> UArray a Double from = unsafeCoerce {-# INLINE to #-} to :: UArray a Double -> UArray a LogFloat to = unsafeCoerce {-# INLINE func #-} func :: (LogFloat -> a -> LogFloat) -> (Double -> a -> Double) func = unsafeCoerce instance IArray UArray LogFloat where {-# INLINE bounds #-} bounds = bounds . from {-# INLINE numElements #-} numElements = numElements . from {-# INLINE unsafeArray #-} unsafeArray lu = to . unsafeArray lu . unsafeCoerce {-# INLINE unsafeAt #-} unsafeAt = unsafeCoerce . unsafeAt . from {-# INLINE unsafeReplace #-} unsafeReplace arr = to . unsafeReplace (from arr) . unsafeCoerce {-# INLINE unsafeAccum #-} unsafeAccum f arr = to . unsafeAccum (func f) (from arr) {-# INLINE unsafeAccumArray #-} unsafeAccumArray f initialValue lu = to . unsafeAccumArray (func f) (unsafeCoerce initialValue) lu test1 :: [Double] -> Bool test1 elms' = elms == U.elems arr where arr :: UArray Int LogFloat arr = U.listArray (1, length elms) elms elms = map (logFloat . abs) elms' test2 :: [Double] -> Bool test2 elms' = product elms == arr U.! 1 where arr :: UArray Int LogFloat arr = U.accumArray (*) 1 (1, 1) [(1,x) | x <- elms] elms = map (logFloat . abs) elms' main :: IO () main = quickCheck test1 >> quickCheck test2 -- Felipe.