I've been playing with generics in general (pardon the pun) and Uniplate in particular, and found out that strict data fields somehow derail Uniplate.
Observe:
=== code ===
{-# LANGUAGE DeriveDataTypeable #-}
module Test where
import Data.Generics (Data(..),Typeable(..))
import Data.Generics.PlateData
import Data.ByteString
import Data.ByteString.Char8 as C
data Foo = Foo String deriving (Show, Data, Typeable)
tst1 = [ Foo "a", Foo "b" ]
test1 = [ show x | Foo x <- universeBi tst1 ]
-- *Test> test1
-- ["\"a\"","\"b\""]
data Bar = Bar ByteString deriving (Show, Data, Typeable)
tst2 = [ Bar (C.pack "a"), Bar (C.pack "b") ]
test2 = [ show x | Bar x <- universeBi tst2 ]
-- *Test> test2
-- *** Exception: Prelude.undefined
=== end of code ===
First, I thought that instance of Data for ByteString is somehow deficient, but this is not the case.
If you change definition of Foo to "data Foo = Foo !String", you would get the same error with "Prelude.undefined".
Since all fields in ByteString constructors are strict, I have no joy trying to use it with Uniplate.
Howere, my type-foo is not strong enough to understand what's wrong. Could someone give me a hint?
PS
ghc 6.10.4
uniplate 1.2.0.3
bytestring 0.9.1.4
PPS
Neil Mitchell is receiving a copy of this email