retrie: A powerful, easy-to-use codemodding tool for Haskell.

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

Retrie is a tool for codemodding Haskell. Key goals include:

This package provides a command-line tool (retrie) and a library (Retrie) for making equational edits to Haskell code.

Please see the README for examples and usage.


[Skip to Readme]

Properties

Versions 0.1.0.0, 0.1.0.0, 0.1.0.1, 0.1.1.0, 0.1.1.1, 1.0.0.0, 1.1.0.0, 1.2.0.0, 1.2.0.1, 1.2.1, 1.2.1.1, 1.2.2, 1.2.3
Change log CHANGELOG.md
Dependencies ansi-terminal (>=0.10.3 && <0.11), async (>=2.2.2 && <2.3), base (>=4.11 && <4.14), bytestring (>=0.10.8 && <0.11), containers (>=0.5.11 && <0.7), data-default (>=0.7.1 && <0.8), directory (>=1.3.1 && <1.4), filepath (>=1.4.2 && <1.5), ghc (>=8.4 && <8.10), ghc-exactprint (>=0.6.2 && <0.7), haskell-src-exts (>=1.23.0 && <1.24), mtl (>=2.2.2 && <2.3), optparse-applicative (>=0.15.1 && <0.16), process (>=1.6.3 && <1.7), random-shuffle (>=0.0.4 && <0.1), retrie, syb (>=0.7.1 && <0.8), text (>=1.2.3 && <1.3), transformers (>=0.5.5 && <0.6), unordered-containers (>=0.2.10 && <0.3) [details]
License MIT
Copyright Copyright (c) Facebook, Inc. and its affiliates.
Author Andrew Farmer <anfarmer@fb.com>
Maintainer Andrew Farmer <anfarmer@fb.com>
Category Development
Uploaded by AndrewFarmer at 2020-03-16T18:24:22Z

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for retrie-0.1.0.0

[back to package description]

Retrie is a powerful, easy-to-use codemodding tool for Haskell.

Install

cabal update
cabal install retrie

Example

Assume you have some code, including functions like foo:

module MyModule where

foo :: [Int] -> [Int]
foo ints = map bar (map baz ints)

Someone points out that traversing the list ints twice is slower than doing it once. You could fix the code by hand, or you could rewrite it with retrie:

retrie --adhoc "forall f g xs. map f (map g xs) = map (f . g) xs"

Retrie applies the equation as a rewrite to all the Haskell modules it finds in the current directory:

 module MyModule where

 foo :: [Int] -> [Int]
-foo ints = map bar (map baz ints)
+foo ints = map (bar . baz) ints

Of course, now you might find this code more difficult to understand. You also learn that GHC will do this sort of optimization automatically, so you decide to undo your rewrite:

retrie --adhoc "forall f g xs. map (f . g) xs = map f (map g xs)"

Now you have your original code back.

Other Sources Of Equations

To try some examples, put the following into MyModule2.hs:

module MyModule2 where

maybe :: b -> (a -> b) -> Maybe a -> b
maybe d f mb = case mb of
  Nothing -> d
  Just x -> f x

type MyMaybe = Maybe Int

{-# RULES "myRule" forall x. maybe Nothing Just x = x #-}

foo :: Maybe Int
foo = maybe Nothing Just (Just 5)

Then try the following rewrites and check the contents of the module after each step:

retrie --type-backward MyModule2.MyMaybe
 module MyModule2 where

 maybe :: b -> (a -> b) -> Maybe a -> b
 maybe d f mb = case mb of
   Nothing -> d
   Just x -> f x

 type MyMaybe = Maybe Int

 {-# RULES "myRule" forall x. maybe Nothing Just x = x #-}

-foo :: Maybe Int
+foo :: MyMaybe
 foo = maybe Nothing Just (Just 5)
retrie --unfold MyModule2.maybe
 module MyModule2 where

 maybe :: b -> (a -> b) -> Maybe a -> b
 maybe d f mb = case mb of
   Nothing -> d
   Just x -> f x

 type MyMaybe = Maybe Int

-{-# RULES "myRule" forall x. maybe Nothing Just x = x #-}
+{-# RULES "myRule" forall x. case x of
+            Nothing -> Nothing
+            Just x1 -> Just x1 = x #-}

 foo :: MyMaybe
-foo = maybe Nothing Just (Just 5)
+foo = case Just 5 of
+  Nothing -> Nothing
+  Just x -> Just x
retrie --fold MyModule2.maybe
 module MyModule2 where

 maybe :: b -> (a -> b) -> Maybe a -> b
 maybe d f mb = case mb of
   Nothing -> d
   Just x -> f x

 type MyMaybe = Maybe Int

-{-# RULES "myRule" forall x. case x of
-            Nothing -> Nothing
-            Just x1 -> Just x1 = x #-}
+{-# RULES "myRule" forall x. maybe Nothing Just x = x #-}

 foo :: MyMaybe
-foo = case Just 5 of
-  Nothing -> Nothing
-  Just x -> Just x
+foo = maybe Nothing Just (Just 5)
retrie --rule-forward MyModule2.myRule
 module MyModule2 where

 maybe :: b -> (a -> b) -> Maybe a -> b
 maybe d f mb = case mb of
   Nothing -> d
   Just x -> f x

 type MyMaybe = Maybe Int

 {-# RULES "myRule" forall x. maybe Nothing Just x = x #-}

 foo :: MyMaybe
-foo = maybe Nothing Just (Just 5)
+foo = Just 5
retrie --type-forward MyModule2.MyMaybe
 module MyModule2 where

 maybe :: b -> (a -> b) -> Maybe a -> b
 maybe d f mb = case mb of
   Nothing -> d
   Just x -> f x

 type MyMaybe = Maybe Int

 {-# RULES "myRule" forall x. maybe Nothing Just x = x #-}

-foo :: MyMaybe
+foo :: Maybe Int
 foo = Just 5

Motivation

Refactoring tools fall on a spectrum. At one end is simple string replacement (grep and sed). At the other is parsing an abstract-syntax tree (AST) and directly manipulating it. Broadly, the tradeoffs are:

Retrie finds a middle ground:

Features

See retrie --help for a complete list of options.

Scripting and Side Conditions

Retrie can be used as a library to tackle more complex rewrites.

Consider the task of changing the argument type of a function from String to an enumeration:

fooOld :: String -> IO ()

data FooArg = Foo | Bar

fooNew :: FooArg -> IO ()

Retrie provides a small monadic DSL for scripting the application of rewrites. It also allows you to intercept and manipulate the result of matching the left-hand side of an equation. Putting those two together, you could implement the following refactoring:

{-# LANGUAGE OverloadedStrings #-}
module Main where
  
import Retrie
  
main :: IO ()
main = runScript $ \opts ->
  [rewrite] <- parseRewrites opts [Adhoc "forall arg. fooOld arg = fooNew arg"]
  return $ apply [setRewriteTransformer stringToFooArg rewrite]
  
argMapping :: [(FastString, String)]
argMapping = [("foo", "Foo"), ("bar", "Bar")]
  
stringToFooArg :: MatchResultTransformer
stringToFooArg _ctxt match
  | MatchResult substitution template <- match
  , Just (HoleExpr expr) <- lookupSubst "arg" substitution
  , L _ (HsLit _ (HsString _ str)) <- astA expr = do
    newExpr <- case lookup str argMapping of
      Nothing ->
        parseExpr $ "error \"invalid argument: " ++ unpackFS str ++ "\""
      Just constructor -> parseExpr constructor
    return $
      MatchResult (extendSubst substitution "arg" (HoleExpr newExpr)) template
  | otherwise = return NoMatch

Running this program would create the following diff:

 module MyModule3 where
  
 baz, bar, quux :: IO ()
-baz = fooOld "foo"
+baz = fooNew Foo
 
-bar = fooOld "bar"
+bar = fooNew Bar

-quux = fooOld "quux"
+quux = fooNew (error "invalid argument: quux")

Defining the stringToFooArg function requires knowledge of both the Retrie library and GHC's internal AST types. You'll find haddock/hoogle invaluable for both.

Reporting Bugs/Submitting Patches

To report a bug in the result of a rewrite, please create a test case (example) and submit it as an issue or merge request.

To report other bugs, please create a GitHub issue.

Build Status

License

Retrie is MIT licensed, as found in the LICENSE file.