Trouble with barbies

Hello dear friends.

I’m struggling with barbies.

Consider:

import "base"    GHC.Generics (Generic)
import "base"    Data.Functor.Identity (Identity(..))
import "barbies" Data.Functor.Barbie

data A' f = A
    { name   :: f Int
    , thing  :: f Int
    }
    deriving (Generic, FunctorB)

Works fine.

Also fine:

data A' f = A
    { name   :: f Int
    , thing  :: [f Int]
    }
    deriving (Generic, FunctorB)

(thing is now a list of f Int)

But …

data A' f = A
    { name   :: f Int
    , thing  :: f [f Int]
    }
    deriving (Generic, FunctorB)

(thing now an f [f int] fails with:

<interactive>:5:24: error:
    • No instance for (barbies-2.0.4.0:Barbies.Generics.Functor.GFunctor
                         0
                         f
                         g
                         (Rec (barbies-2.0.4.0:Data.Generics.GenericN.Param 0 f [barbies-2.0.4.0:Data.Generics.GenericN.Param 0 f Int]) (f [f Int]))
                         (Rec (barbies-2.0.4.0:Data.Generics.GenericN.Param 0 g [barbies-2.0.4.0:Data.Generics.GenericN.Param 0 g Int]) (g [g Int])))
        arising from the 'deriving' clause of a data type declaration
      Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself
    • When deriving the instance for (FunctorB A')

)

So okay, plan 1, can I make it a different argument (and live with having to write the desired type twice)? No

data A' f g = A
    { name   :: f Int
    , thing  :: f [g Int]
    }
    deriving (Generic, FunctorB)

Gives:

<interactive>:5:24: error:
    • No instance for (barbies-2.0.4.0:Barbies.Generics.Functor.GFunctor
                         0 f1 g (Rec (f [barbies-2.0.4.0:Data.Generics.GenericN.Param 0 f1 Int]) (f [f1 Int])) (Rec (f [barbies-2.0.4.0:Data.Generics.GenericN.Param 0 g Int]) (f [g Int])))
        arising from the 'deriving' clause of a data type declaration
      Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself
    • When deriving the instance for (FunctorB (A' f))

Plan 2, can I make a new type that hides things?

data A' f g  = A
    { name  :: f Int
    , thing :: f [X' g]
    }
    deriving (Generic, FunctorB)

newtype X' g = X { x :: g Int }
  deriving (Generic, FunctorB)

Yep!

But wait, can I just remove that g now?

data A' f  = A
    { name  :: f Int
    , thing :: f [X' f]
    }
    deriving (Generic, FunctorB)

newtype X' g = X { x :: g Int }
  deriving (Generic, FunctorB)

No.

<interactive>:7:11: error:
    • No instance for (barbies-2.0.4.0:Barbies.Generics.Functor.GFunctor
                         0
                         f
                         g
                         (Rec (barbies-2.0.4.0:Data.Generics.GenericN.Param 0 f [X' (barbies-2.0.4.0:Data.Generics.GenericN.Param 0 f)]) (f [X' f]))
                         (Rec (barbies-2.0.4.0:Data.Generics.GenericN.Param 0 g [X' (barbies-2.0.4.0:Data.Generics.GenericN.Param 0 g)]) (g [X' g])))
        arising from the 'deriving' clause of a data type declaration
      Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself
    • When deriving the instance for (FunctorB A')

But wait, what if I do something crazy and introduce a meaningless field:

data A' f g  = A
    { name  :: f Int
    , thing :: f [X' f]
    , meaningless :: g Int
    }
    deriving (Generic, FunctorB)

newtype X' g = X { x :: g Int }
  deriving (Generic, FunctorB)

Yep!

Does this work on the original scheme? Yep.

data A' f g = A
    { name   :: f Int
    , thing  :: f [f Int]
    , meaningless :: g Int
    }
    deriving (Generic, FunctorB)

Please help. What is going on?!

2 Likes

And does it work if you keep g as an argument but remove the meaningless field? That is,

data A' f g = A
    { name   :: f Int
    , thing  :: f [f Int]
    }
    deriving (Generic, FunctorB)
1 Like

Thanks for taking a look @tomjaguarpaw; sorry, I should’ve posted that option; unfortunately not:

<interactive>:5:24: error:
    • Cannot derive well-kinded instance of form ‘FunctorB (A' ...)’ Class ‘FunctorB’ expects an argument of kind ‘(* -> *) -> *’
    • In the data declaration for ‘A'’

Ah! But does it work if you give g a kind signature? For example

data A' f (g :: * -> *) = A
    { name   :: f Int
    , thing  :: f [f Int]
    }
    deriving (Generic, FunctorB)
1 Like

Ah, indeed it does …

:ponder: so is this my best option? I guess it’s somehow a bug in the barbie library?

Using the Wear part of the API I get a slightly different error, and actually only on the Covered instance:

data A' t f = A
    { name   :: Wear t f Int
    , thing  :: Wear t f [Wear t f Int]
    }
    deriving (Generic)
    
instance FunctorB (A' Bare)
instance FunctorB (A' Covered)
<interactive>:7:10: error:
    • No instance for (barbies-2.0.4.0:Barbies.Generics.Functor.GFunctor
                         0
                         f
                         g
                         (Rec (barbies-2.0.4.0:Data.Generics.GenericN.Param 0 f [barbies-2.0.4.0:Data.Generics.GenericN.Param 0 f Int]) (f [f Int]))
                         (Rec (barbies-2.0.4.0:Data.Generics.GenericN.Param 0 g [barbies-2.0.4.0:Data.Generics.GenericN.Param 0 g Int]) (g [g Int])))
        arising from a use of ‘barbies-2.0.4.0:Barbies.Internal.FunctorB.$dmbmap’
    • In the expression: barbies-2.0.4.0:Barbies.Internal.FunctorB.$dmbmap @(*) @(A' Covered)
      In an equation for ‘bmap’: bmap = barbies-2.0.4.0:Barbies.Internal.FunctorB.$dmbmap @(*) @(A' Covered)
      In the instance declaration for ‘FunctorB (A' Covered)’

I guess the problem is something like there are two places to run the functor, and it doesn’t know which to pick? (when really it should just do both?) ; but I don’t get why adding the extra argument helps.

Also, adding the extra argument breaks other normal barbie things (in my above example) i.e. precisely bmap itself, as it transforms the wrong type argument :frowning:

I think that answers your question: adding the extra argument makes barbies do something completely different; it just ignores the problem with the original argument.

Indeed, so I’m really hoping there’s a problem to the central issue :slight_smile:

@marcosh has helped me solve it; here’s the answer:

newtype Thing (f :: * -> *) =  Thing { getThing :: [f Int] }
  deriving (Generic, Typeable)

instance FunctorB Thing

deriving instance (Show (f Int)) => Show (Thing f)
deriving instance (Eq (f Int))   => Eq (Thing f)

data A' f' f = A
  { name  :: f' String
  , thing :: f' (Thing f) }
  deriving (Generic)

instance FunctorT A'
instance Functor f' => FunctorB (A' f')

deriving instance (Show (Thing f), Show (f' (Thing f)), Show (f' String)) => Show (A' f' f)

type A f = A' f f

a :: A Identity
a = A (pure "name") (pure $ Thing [pure 1, pure 2, pure 3])

b :: A Maybe
b = btmap1 (Just . runIdentity) a
3 Likes

Maybe at this point it is simply more convenient to define the FunctorB instance (by implementing the bmap function) yourself, instead of having to wrap your ‘thing’ field with a useless Thing newtype?

edit: actually, thinking a bit about it; it may be that you simply cannot make your type

into a functorB, since it seems you need that f (or g) is an instance of Functor to transform the ‘f [f Int]’, into a ‘f [g Int]’ (after which you can then transform it into a ‘g [g Int’]) using the argument of bmap. (Or am I overlooking something?) However, since ‘f’ and ‘g’ are unconstrained in the type of bmap I’m guessing you may simply not be able to implement them.

edit2: I guess that is at least consistent with the version that used the additional Thing newtype (where you explicitly made the f’ visible, so you could constrain it to be an instance of Functor)

If anyone wants to keep playing, there still seems to be an issue when you embed something like A' in yet another barbie:

newtype Thing (f :: * -> *) =  Thing { getThing :: [f Int] }
  deriving (Generic, FunctorB)

deriving instance (Show (f Int)) => Show (Thing f)

data A' f' f = A
  { name  :: f' String
  , thing :: f' (Thing f)
  }
  deriving (Generic)

instance FunctorT A'
instance Functor f' => FunctorB (A' f')

deriving instance (Show (f' (Thing f)), Show (f' String)) => Show (A' f' f)

newtype B' f' f = B
  { someA :: f' (A f)
  }
  deriving Generic

instance FunctorT B'
instance Functor f' => FunctorB (B' f')

type A f = A' f f
type B f = B' f f

a :: A Identity
a = A (pure "name") (pure $ Thing [pure 1, pure 2, pure 3])

a' :: A Maybe
a' = btmap1 (Just . runIdentity) a

--b :: B Identity
--b = B a

Here’s the error:

<interactive>:17:10: error:
    • Could not deduce (barbies-2.0.4.0:Barbies.Generics.Functor.GFunctor
                          0 f g (Rec (f' (A (barbies-2.0.4.0:Data.Generics.GenericN.Param 0 f))) (f' (A f))) (Rec (f' (A (barbies-2.0.4.0:Data.Generics.GenericN.Param 0 g))) (f' (A g))))
        arising from a use of ‘barbies-2.0.4.0:Barbies.Internal.FunctorB.$dmbmap’
      from the context: Functor f' bound by the instance declaration at <interactive>:17:10-39
    • In the expression: barbies-2.0.4.0:Barbies.Internal.FunctorB.$dmbmap @(*) @(B' f')
      In an equation for ‘bmap’: bmap = barbies-2.0.4.0:Barbies.Internal.FunctorB.$dmbmap @(*) @(B' f')
      In the instance declaration for ‘FunctorB (B' f')’

it’s basically the same problem, but now of 3 arguments instead of two, and hence can’t be resolved trivially with FunctorT.

If anyone has thoughts I’d appreciate it! :pray:

Have you looked at barbies-layered: Barbies with layered clothes.? It might provide some inspiration.

1 Like

Thanks this looks great; I’ll take a glance!

If you’re going to use two-parameter types like

consider switching to deep-transformations which takes that idea and builds on top of it. The library is layered on top of rank2classes rather than barbies. The names of the generic functions would change, and you’d use Template Haskell splices instead of generic deriving, but the core functionality is much the same.

Alternatively, you can have a look at hypertypes which is supposed to solve the same problem but in a completely different way. I haven’t used it myself so I can’t vouch for it, whereas I’m the author and maintainer of the aforementioned deep-transformations so I can at least guarantee it’s maintained.

2 Likes

Therebis also by semi-abandonned package metamorphosis which uses TemplateHaskell to duplicate and transform records (you get a real flat records for each barbie clothes) and most importantly conversion function between them.

Edit

I am terrible at writing doc so to summarize, metamorphosis allows to take a type (record and/or sum types) run some search/replace operation on each field (you can change the name, the type and even the constructor) and end up with one or more new records with one or more constructors.
Metamorphosis remember the link between the fields of the old and new records and generate conversion function between them.

For example you have

data A = A { x :: Int
                  , y :: Int
                  }

That can be translated to the table

Type.Constructor.field type
A.A.x Int
A.A.y Int

You could some sed to transforme it to

B.X.x Int
B.Y.y Int

and that would generate

data B = X { x :: Int }
            |  Y { Y :: Int }

and aToB :: A -> (B, B), (B, B) -> A.

or

C.C.x Maybe Int
C.C.y Maybe Int

and get

data C = C { x :: Maybe Int 
                   , y :: Maybe Int
                   }

and aToC :: A -> Maybe C, etc …

In theory you can even convert multiple type to multiple type as in

data P = P { x , y :: Int }
data Q = Q { z :: Int }

By replacing

P.P.x    ->   R.R.x
P.P.y    ->   S.S.y
Q.Q.z  ->   S.S.z

Metamorphis will generate

data R = R { x :: Int }
data S = S { y, z :: Int }

and pqToRs :: P -> Q -> (R,S).