hoop: Object-Oriented Programming in Haskell

[ language, library, mit ] [ Propose Tags ] [ Report a vulnerability ]

Library for object-oriented programming in Haskell.


[Skip to Readme]

Modules

  • Language
    • Language.MSH
      • Language.MSH.BuiltIn
      • Language.MSH.CodeGen
        • Language.MSH.CodeGen.Class
        • Language.MSH.CodeGen.Constructors
        • Language.MSH.CodeGen.Data
        • Language.MSH.CodeGen.Decls
        • Language.MSH.CodeGen.Inheritance
        • Language.MSH.CodeGen.Instances
        • Language.MSH.CodeGen.Interop
        • Language.MSH.CodeGen.Invoke
        • Language.MSH.CodeGen.Methods
        • Language.MSH.CodeGen.MiscInstances
        • Language.MSH.CodeGen.Monad
        • Language.MSH.CodeGen.New
        • Language.MSH.CodeGen.NewInstance
        • Language.MSH.CodeGen.Object
        • Language.MSH.CodeGen.ObjectInstance
        • Language.MSH.CodeGen.PrimaryInstance
        • Language.MSH.CodeGen.Shared
        • Language.MSH.CodeGen.SharedInstance
      • Language.MSH.Constructor
      • Language.MSH.MethodTable
      • Language.MSH.NewExpr
      • Language.MSH.Parsers
      • Language.MSH.Pretty
      • Language.MSH.QuasiQuoters
      • Language.MSH.RuntimeError
      • Language.MSH.Selectors
      • Language.MSH.StateDecl
      • Language.MSH.StateEnv

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.3.0.0
Dependencies base (>=4.7 && <5.0), containers, haskell-src-exts (>=1.16), haskell-src-meta (>=0.6), lens (>=4.10), mtl (>=2.1), parsec (>=3.1.9), pretty, template-haskell (>=2.14), text [details]
License MIT
Copyright Copyright (c) Michael B. Gale
Author Michael B. Gale
Maintainer [email protected]
Category Language
Home page https://github.com/mbg/hoop#readme
Bug tracker https://github.com/mbg/hoop/issues
Source repo head: git clone https://github.com/mbg/hoop
Uploaded by mbg at 2020-07-04T19:10:34Z
Distributions
Downloads 266 total (5 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs not available [build log]
Last success reported on 2020-07-04 [all 2 reports]

Readme for hoop-0.3.0.0

[back to package description]

hoop

A Haskell library for object-oriented programming which allows programmers to use objects in ordinary Haskell programs. In particular, the library achieves the following design objectives (to avoid ambiguity with Haskell's type classes, we refer to classes in the object-oriented sense as object classes):

  • No extensions to the Haskell language are required beyond what is already implemented in GHC. Object classes are generated from Template Haskell quasi quotations using an OO-like syntax where the methods are defined as ordinary Haskell expressions.
  • Object classes can be instantiated from ordinary Haskell code (with an overloaded function named new). The resulting objects are ordinary Haskell values and can be used as such.
  • Calling methods on objects can be done from within ordinary Haskell code.
  • The objects do not rely on IO. Instantiating objects and calling methods on the resulting objects is pure.
  • Object classes can inherit from other object classes, which also established subtyping relations between them. There is no limit to how deep these inheritance trees may grow.
  • Class hierarchies are open for extension. I.e. the library does not need to know about all subclasses of a given class in order to generate the code for that class, allowing modular compilation.
  • Casting from subtype objects to their supertypes is supported and the types are correctly reflected in Haskell's type system (e.g. assuming that we have Duck <: Bird and that obj :: Duck then upcast obj :: Bird) and pure.
  • Type annotations are generally not required except where something would logically be ambiguous otherwise (e.g. instantiating an object with the new function).

Examples

The test folder contains a number of examples of the library in action, illustrating the various features.

As a quick tutorial, a simple expression language can be implemented using the library as shown below. Note that the bodies of the two implementations of the eval method are ordinary Haskell expressions. The .! operator is an ordinary Haskell operator used to call methods on objects and this is just an ordinary Haskell definition, too.

[state|
abstract state Expr where
    eval :: Int

state Val : Expr where
    data val = 0 :: Int

    eval = do
        r <- this.!val
        return r

state Add : Expr where 
    data left :: Expr 
    data right :: Expr 

    eval = do 
        x <- this.!left.!eval 
        y <- this.!right.!eval 
        return (x+y)
|]

someExpr :: Add 
someExpr = new @Add (upcast $ new @Val 4, upcast $ new @Val 7)

someExprResult :: Int 
someExprResult = result (someExpr.!eval)

If we evaluate someExprResult, the result is 11 as expected. We can note some points of interest here that differ from popular object-oriented programming languages:

  • The type annotations on someExpr and someExprResult are optional and just provided for clarity. The type applications for the calls to new are required (alternatively, type annotations on the sub-expression would work, too).
  • Casts must be explicit: in the example, the objects of type Val must be explicitly cast to Expr values to instantiate the Add object.
  • Since everything is pure, calling a method on an object produces two results: the result of the method call and a (potentially) updated object. The result function returns the result of calling eval on the someExpr object, discarding the resulting object.
  • It does not matter what type of object we call eval on, as long as it is of type Expr or is a sub-type of Expr.

Indeed, we can cast the Add object to an Expr object, call eval on it, and still get the correct result:

> let e = upcast someExpr in result (e.!eval)
11
  • Casting from supertype objects to a subtype is possible, but may fail (returning Nothing). E.g. assuming Duck <: Bird and that obj :: Bird then downcast obj :: Maybe Duck.

Overview of the process

  • QuasiQuoters.hs contains the entry point
  • First, the state declarations are parsed (Parsers.hs) via parseStateDecl
  • The parsed declarations are then passed to genStateDecls (Language.MSH.CodeGen.Decls / Decls.hs)
  • This turns the declarations into a dependency graph (via buildStateGraph in Language.MSH.StateEnv / StateEnv.hs)
  • If successful, the graph is written to graph.log
  • The genStateDecl function is then applied to every state declaration in dependency order (i.e. starting from no dependencies)