Git Product home page Git Product logo

rock's Introduction

rock

Build Status CI Status Hackage

A build system inspired by Build systems ร  la carte.

Used in Sixten, Sixty and Eclair to achieve incremental and query driven compiler architectures.

Example

{-# language FlexibleInstances #-}
{-# language GADTs #-}
{-# language StandaloneDeriving #-}
{-# language TemplateHaskell #-}

import Control.Monad.IO.Class
import Data.GADT.Compare.TH (deriveGEq)
import Data.Hashable
import Data.Some
import Data.IORef
import qualified Rock

data Query a where
  A :: Query Integer
  B :: Query Integer
  C :: Query Integer
  D :: Query Integer

deriving instance Show (Query a)
deriveGEq ''Query

instance Hashable (Query a) where
  hashWithSalt salt query =
    case query of
      A -> hashWithSalt salt (0 :: Int)
      B -> hashWithSalt salt (1 :: Int)
      C -> hashWithSalt salt (2 :: Int)
      D -> hashWithSalt salt (3 :: Int)

instance Hashable (Some Query) where
  hashWithSalt salt (Some query) = hashWithSalt salt query

rules :: Rock.Rules Query
rules key = do
  liftIO $ putStrLn $ "Fetching " <> show key
  case key of
    A -> pure 10
    B -> do
      a <- Rock.fetch A
      pure $ a + 20
    C -> do
      a <- Rock.fetch A
      pure $ a + 30
    D ->
      (+) <$> Rock.fetch B <*> Rock.fetch C

main :: IO ()
main = do
  do
    liftIO $ putStrLn "Running"
    result <- Rock.runTask rules (Rock.fetch D)
    print result
  do
    liftIO $ putStrLn "Running with memoisation"
    memoVar <- newIORef mempty
    result <- Rock.runTask (Rock.memoise memoVar rules) (Rock.fetch D)
    liftIO $ print result

Prints

Running
Fetching D
Fetching B
Fetching A
Fetching C
Fetching A
70
Running with memoisation
Fetching D
Fetching B
Fetching A
Fetching C
70

Note: Besides pure computations as shown above, the Task data type implements MonadIO, so you can lift IO actions into the Task monad by using liftIO!

Query parameters

If you need to parametrize your queries (e.g. typechecking one specific file), you can do this by adding additional arguments to your Query datatype:

data Query a where
  Parse :: FilePath -> Query AST
  Typecheck :: FilePath -> Query (Either TypeError TypedAST)

rules :: Rock.Rules Query
rules key = case key of
  Parse file -> do
    _ -- parse the file..
  Typecheck file -> do
    ast <- Rock.fetch (Parse file)
    _ -- typecheck file..

Related projects

Contributions

... are very welcome, especially in the areas of documentation and examples.

rock's People

Contributors

ollef avatar kpadmasola avatar luc-tielen avatar smunix avatar

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.