5

What is the best way to make

type Configuration = Array DIM1 (Double, Double, Double)

an instance of Read? So later I could derive

data SimulationData = SD Configuration Double StdGen Int

to be an instance of Read too.

Yrogirg
  • 2,301
  • 3
  • 22
  • 33
  • I suspect you can't make a "full" Read instance. Generally, important datatypes will already have Read instances if the author believes they make sense. The `Array` type in Repa has higher order functions inside its components - `Generator` and `Range` which cannot be made instances of Read. I'd imagine the correct thing to do is serialize / de-serialize your data into a simpler format. – stephen tetley Dec 24 '11 at 16:39

1 Answers1

6

Such an instance will be an orphan instance, which you should generally avoid. However, it's fairly simple to write it:

{-# LANGUAGE TypeOperators #-}

import Data.Array.Repa (Array, Shape, Elt, Z(..), (:.)(..))
import qualified Data.Array.Repa as R

instance Read Z where
  readsPrec _ r = do
    ("Z", s) <- lex r
    return (Z, s)

instance (Read tail, Read head) => Read (tail :. head) where
  readsPrec d =
    readParen (d > prec) $ \r -> do
      (tl, s) <- readsPrec (prec + 1) r
      (":.", t) <- lex s
      (hd, u) <- readsPrec (prec + 1) t
      return (tl :. hd, u)
    where prec = 3

instance (Shape sh, Read sh, Elt a, Read a) => Read (Array sh a) where
  readsPrec d =
    readParen (d > app) $ \r -> do
      ("Array", s) <- lex r
      (sh, t) <- readsPrec (app + 1) s
      (xs, u) <- readsPrec (app + 1) t
      return (R.fromList sh xs, u)
    where app = 10

If you use the StandaloneDeriving extension, the first two instances can be simplified:

deriving instance Read Z
deriving instance (Read tail, Read head) => Read (tail :. head)

These instances should probably be in repa itself; I just based them on the example instance given in Text.Show and repa's show output. I suggest making a feature request on repa's bug tracker, and putting these instances into a module of your program for now (unless you want to avoid orphan instances entirely, in which case you'll have to solve the problem another way altogether).


That said, you should probably consider simply converting your data to a list (with toList) and using that; it avoids the orphan instance, and shouldn't have any downsides. You might also want to consider using a "real" serialisation library like cereal if you're more interested in processing the data with code than having it be human-readable; Read is generally considered to be of rather limited use.

ehird
  • 40,602
  • 3
  • 180
  • 182
  • The `Array` type in Repa is made from a list of Regions which contain `Range` and `Generator`, both Range an Generator have higher-order functions as components so they can't really be made instances of Read. – stephen tetley Dec 24 '11 at 16:33
  • @stephentetley: All a `Read` instance has to be able to do is parse the valid Haskell code that the corresponding `Show` instance outputs. – ehird Dec 24 '11 at 16:58
  • `show $ R.fromFunction (Z :. (10::Int)) (const 42)` = `"Array (Z :. 10) [42.0,42.0,42.0,42.0,42.0,42.0,42.0,42.0,42.0,42.0]"`, which my instance parses correctly. – ehird Dec 24 '11 at 16:59
  • Admittedly, repa's `Show` instance is breaking the rules here, as that code doesn't type, but that rule is frequently bent (e.g. `Data.ByteString.Char8` exports a `Show` instance for ByteStrings which only works if you turn on `OverloadedStrings`, and I think the `Show` instance for lazy ByteStrings actually uses unexported constructors). – ehird Dec 24 '11 at 17:02
  • @ehird: Requiring `Show` and `Read` to be semantically valid Haskell serves little practical purpose. Syntax matters, however, as it would otherwise be difficult to define well-behaved instances for container types like `[a]` which have to cooperate with the instances for the element type. – hammar Dec 24 '11 at 17:56
  • @hammar: Yes, that's a fair view. I consider `Show` basically only useful for debugging (which it's very useful for, of course), and `Read` only useful for toy programs, so I may value semantically valid instances more than others. – ehird Dec 24 '11 at 17:59
  • @ehird, there is a problem. I can't parse for example `Just arr`, it gives me "*** Exception: Prelude.read: no parse", though parsing arrays themselves or tuples works. – Yrogirg Dec 25 '11 at 16:43
  • 1
    @Yrogirg: This is a bug in repa's `Show` instance: it shows `Just arr` as `Just Array (Z :. 10) [...]`, without the required parentheses. Changing `readsPrec d = readParen (d > app) $ \r -> do` to `readsPrec d r = do` should make my instance work in this case, but unfortunately what repa is doing causes inherent ambiguity; you should report it as a bug. – ehird Dec 25 '11 at 17:05