Giter Club home page Giter Club logo

Comments (6)

jcpetruzza avatar jcpetruzza commented on June 24, 2024 1

Version 2.0.0.0 supports nested barbies via bifunctors. See https://hackage.haskell.org/package/barbies-2.0.0.0/docs/Barbies.html#g:3

from barbies.

jcpetruzza avatar jcpetruzza commented on June 24, 2024 1

Hi @yairchu, the quote was not mine, but I think the general idea of using barbies for ASTs would be something along the lines of:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}

-- NB. I'm adding a Let constructor that wasn't in your example
data Expr (f :: String -> Type)
  = Var (f "Var") Text
  | App (f "App") (Expr f) (Expr f)
  | Let (f "Let") Text (Expr f)
  | Lam (f "Lam") Text (Typ f) (Expr f)

data Typ (f :: String ->  Type)
  = IntT (f "IntT")
  | FuncT (f "FuncT") (Typ f) (Typ f)

-- NB. Unit is Barbies.Unit
data TypeCheckedAndDesugared (s :: String) where
  CVar :: (Typ Unit) -> TypeCheckedAndDesugared "Var"
  CApp :: Unit -> TypeCheckedAndDesugared "App"
  CLam :: Typ Unit -> TypeCheckedAndDesugared "Lam"

Now, if you get something of type Expr TypeCheckedAndDesugared you know that:

  • Variables (in Var and Lam) have been annotated with their type (must have happened during typecheck)
  • Applications have no annotation (Unit)
  • There are no Let constructors (so they've been "desugared")

Now, in this example, Expr and Typ don't occur in TypeCheckedAndDesugared, so the "nested" part is not mandatory for this to work, but may be needed depending what you want to achieve.

Hope this makes sense! (the example is untested, but should hopefully work after minor fixes)

from barbies.

jcpetruzza avatar jcpetruzza commented on June 24, 2024 1

So the given f isn't used to contain the AST subexpressions but rather it is only used for node annotations, right?

At least in my example, yeah.

To explain what I mean, if it was for nesting AST subexpressions, one could use Either String as clothes of a partially parsed AST with the parse errors only being on specific sub-trees. Can barbies also be nested this way?

Let me see if I understand. You'd like something like:

data Expr f 
  = Var Text
   | App (f (Expr f)) (f (Expr f))
   | Lam Text (f (Expr f))

So that Expr (Either String) is an AST that could contain parse errors, e.g. the lhs of the App is ok, but the rhs is an error message. It is not possible to get an instance of FunctorB Expr: if you try to do it by hand, you'll notice that you are missing a Functor f constraint.

What you could do:

  1. Handle nesting as mentioned in the docs. Ergonomics will probably not be great, though.
  2. Instead of nesting, add an Invalid (f "Invalid") constructor to my example from above. Then a malformed expression could be something like:
example :: Expr MaybeParsed
example = App ParsedApp (Var ParsedVar x) (Invalid (ParseError "syntax error: expected blah..."))

data Parsed err (t :: String) where
  ParsedVar :: Parsed err "Var"
  ParsedApp :: Parsed err "App"
  ParsedLam :: Parsed er "Lam"
  ParseError :: err -> Parsed err "Invalid"

type MaybeParsed = Parsed String

-- An `Expr ParsedOk` has no parsing errors
type ParsedOk = Parsed Void
  1. Define your own specialization of FunctorB, etc:
class MyFunctorB b where
  mybmap :: (forall a . Functor f => f a -> g a) -> b f -> b g

instance MyFunctorB Expr where
  mybmap h = .... 

from barbies.

jcpetruzza avatar jcpetruzza commented on June 24, 2024

Indeed, nested barbies would be quite useful to support, but they proved to be tricky so far. The main issue is that they just don't fit. Let's take OuterBarbie from your gist above and let's try to write an instance FunctorB OuterBarbie

data InnerBarbie f
  = InnerBarbie
  { innerData :: f String
  } deriving (Generic, FunctorB)


data OuterBarbie f
  = OuterBarbie
  { innerBarbie :: f (InnerBarbie f)
  } 

instance FunctorB OuterBarbie where
  bmap h (OuterBarbie fibf)
    = -- because InnerBarbie is a FunctorB, we can use `bmap h` on it; we only need to
      -- pass it through the outer f with an `fmap`; unfortunately this won't typecheck...
      OuterBarbie (bmap h <$> fibf)  

The problem is that, because of the fmap, for this to work we need a Functor f constraint somewhere, and we have nowhere to require it: not in the instance context, since f is not mentioned there; not in the the type of bmap, since we don't want to lose generality. I don't see how AllB or AllBF could save us here either.

All that said, I've been playing recently with a construction that may let us express nested barbies, hopefully without hurting usability too much (it requires QualifiedConstraints, though, so it would be ghc 8.6+ only). First, let's introduce a class analogous to FunctorB, but operating on the next to last type argument:

class Functor2B b where
  bmap2 :: (forall a . f a -> g a) -> b f x -> b g x

We can derive generic instances for this class in the same way. Intuitively, if b is both a Functor2B and a FunctorB, it is a BifunctorB:

type BifunctorB b = (Functor2B b, (forall f. FunctorB (b f)))
 
bfirst :: BifunctorB b => (forall a. f a -> f' a) -> b f g -> b f' g
bfirst = bmap2

bsecond :: BifunctorB b => (forall a. g a -> g' a) -> b f g -> b f g'
bsecond = bmap

(Functor2B also let us give a barbie-interface to monad-transformers, etc).

Now, let's rewrite OuterBarbie as follows (manual instances are for clarity):

data OuterBarbie' f g
  = OuterBarbie' (f (InnerBarbie g))

type OuterBarbie f = OuterBarbie' f f

instance Functor2B OuterBarbie' where
  bmap2 h (OuterBarbie' fibg)
    = OuterBarbie' (h fibg)

instance Functor f => FunctorB (OuterBarbie' f) where
  bmap h (OuterBarbie' fibg)
    = OuterBarbie (bmap h <$> fibg)

Notice that, because of the Functor f constraint, OuterBarbie' is not a BifunctorB. And now we can use the (Co)Yoneda-trick: (Co)Yoneda f is isomorphic to f and has a Functor instance regardless of f. So we can write:

newtype Nested b f
  = Nested (b (Yoneda f) f)

asNested :: (Functor2B b, Functor f) => b f f -> Nested b f
asNested bff
  = Nested (bmap2 liftYoneda bff)

runNested :: Functor2B b => Nested b f -> b f f
runNested (Nested byf)
  = bmap2 lowerYoneda byf

instance (Functor2B b, (forall f. FunctorB (b (Yoneda f) f)) => FunctorB (Nested b f) where
  bmap h (Nested byf)
    = Nested $ bmap2 (hoistYoneda h) $ bmap h byf

So, in the end this means that to work with nested barbies, one would need something like runNested $ bmap h $ asNested outerBarbie. There's an ongoing implementation (still early) in #14. Thoughts welcome!

from barbies.

yairchu avatar yairchu commented on June 24, 2024

This would be very useful e.g. for compilers with rich ASTs, using the clothing types to make fields optional or label fields with source locations and the text they were parsed from, but I can't get it to work.

@jcpetruzza can you give an AST example?
That is, for example can an AST such as the following be represented as nested barbies somehow?

data Expr
    = Var Text
    | App Expr Expr
    | Lam Text Typ Expr
data Typ
    = IntT
    | FuncT Typ Typ

from barbies.

yairchu avatar yairchu commented on June 24, 2024

@jcpetruzza Thanks for the elaboration!

So the given f isn't used to contain the AST subexpressions but rather it is only used for node annotations, right?

To explain what I mean, if it was for nesting AST subexpressions, one could use Either String as clothes of a partially parsed AST with the parse errors only being on specific sub-trees. Can barbies also be nested this way?

from barbies.

Related Issues (20)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.