Home
Members
Publications
Projects/Collab.
Software
Events
Open Positions
Contact
News
Go to: Tool Homepage - Downloads - User Guide - Examples
(This page is based on version 0.3, dowload the code from the example page)
module Expr where data Expr = Const Int | Add (Expr,Expr) e1 = Add (Add (Const 1,Const 2),Const 3) e2 = Add (Add (Const 0,Const 1),Const 2) | module Client where import Expr import ToStringMod import EvalMod r1 = print (toString e1) r2 = print (show (eval e1)) r3 = print (toString e2) r4 = print (show (eval e2)) |
module EvalMod where import Expr eval (Const i) = i eval (Add (e1,e2)) = eval e1 + eval e2 | module ToStringMod where import Expr toString (Const i) = show i toString (Add (e1,e2)) = toString e1 ++ "+" ++ toString e2 |
module Expr where data Expr = Const Int | Add (Expr,Expr) fold f0 f1 (Const i) = f0 i fold f0 f1 (Add (e1,e2)) = f1 (((fold f0) f1) e1) (((fold f0) f1) e2) e1 = Add (Add (Const 1,Const 2),Const 3) e2 = Add (Add (Const 0,Const 1),Const 2) | module Client where import Expr import ConstMod (toString,eval) import AddMod (toString,eval) r1 = print (Client.toString e1) toString x = fold ConstMod.toString AddMod.toString x r2 = print (show (Client.eval e1)) eval x = fold ConstMod.eval AddMod.eval x r3 = print (Client.toString e2) r4 = print (show (Client.eval e2)) |
module ConstMod (eval,toString) where eval i = i toString i = show i | module AddMod (eval,toString) where eval x0 x1 = (x0) + (x1) toString x0 x1 = (x0) ++ ("+" ++ (x1)) |
Function-centered architecture → Data-centered architecture
(defvar f1 "eval" ) (defvar f2 "toString" ) (defvar f1mod "EvalMod" ) (defvar f2mod "ToStringMod" ) (defvar f1reducer "fold" ) (defvar f2reducer "fold2" ) (defvar clientmod "Client" ) (defvar f1prefix (concat f1 "_") ) (defvar f2prefix (concat f2 "_") ) ; 1) Introduce definitions for equations ------------------------------------------------------ (haskell-refac-newDefAllEqBodiesIn f1 f1mod) (haskell-refac-newDefAllEqBodiesIn f2 f2mod) ; 2) abstract pattern variables or rec calls on pattern variables ----------------------------- (haskell-refac-generaliseAllRecAppToPatternVariablesInAllLocalDefsIn f1 f1prefix f1mod) (haskell-refac-generaliseAllPatternVariablesInAllLocalDefsIn f1 f1prefix f1mod) (haskell-refac-generaliseAllRecAppToPatternVariablesInAllLocalDefsIn f2 f2prefix f2mod) (haskell-refac-generaliseAllPatternVariablesInAllLocalDefsIn f2 f2prefix f2mod) ; 3) lift the business functions to the top level --------------------------------------------- (haskell-refac-liftAllLocalDefsToTopLevelIn f1 f1prefix f1mod) (haskell-refac-liftAllLocalDefsToTopLevelIn f2 f2prefix f2mod) ; 4) abstract the business functions in the functions of interest ----------------------------- (haskell-refac-generaliseAllIdentsTopLevel f1 f1prefix "f" f1mod) (haskell-refac-forgetTopLevelPrefixed (concat f1 "_gen") f1mod) (haskell-refac-generaliseAllIdentsTopLevel f2 f2prefix "f" f2mod) (haskell-refac-forgetTopLevelPrefixed (concat f2 "_gen") f2mod) ; 5) rename the functions of interest (they have become traversal iterators) ------------------ (haskell-refac-renameTopLevelIdent f1 f1mod f1reducer) (haskell-refac-renameTopLevelIdent f2 f2mod f2reducer) ; 6) reconstruct the functions of interest as calls to the traversal functions ---------------- (haskell-refac-newDefIdentApp f1reducer f1 clientmod) (haskell-refac-newDefIdentApp f2reducer f2 clientmod) (haskell-refac-generaliseIdentIn "r1" clientmod "e1" "x") (haskell-refac-generaliseIdentIn "r2" clientmod "e1" "x") (haskell-refac-liftDefToTopLevel f1 clientmod) (haskell-refac-liftDefToTopLevel f2 clientmod) ; 7) make calls to function of interest appear and move fold operators------------------------- (haskell-refac-foldToplevelDefinition f1 clientmod) (haskell-refac-foldToplevelDefinition f2 clientmod) (haskell-refac-moveDefBetweenModules f1reducer f1mod "Expr") (haskell-refac-moveDefBetweenModules f2reducer f2mod "Expr") (haskell-refac-replaceIdentIn f2reducer f2 clientmod f1reducer) (haskell-refac-removeTopLevelDef f2reducer "Expr") ; 8) move business functions to the data-centered modules and rename them --------------------- (haskell-refac-moveAllDefsOnSuffix f2prefix f2mod) (haskell-refac-moveAllDefsOnSuffix f1prefix f1mod) (haskell-refac-renameAllIdentsIn f1 f1prefix clientmod) (haskell-refac-renameAllIdentsIn f2 f2prefix clientmod) ; 9) clean useless import --------------------------------------------------------------------- (haskell-refac-cleanImportsMod clientmod)
Data-centered architecture → Function-centered architecture
(defvar f1 "eval" ) (defvar f2 "toString" ) (defvar f1mod "EvalMod" ) (defvar f2mod "ToStringMod" ) (defvar f1reducer "fold" ) (defvar clientmod "Client" ) (defvar f1prefix (concat f1 "_") ) (defvar f2prefix (concat f2 "_") ) ;; use specific names for business functions (haskell-refac-renameAllIdentsIn2 f1 f1 f1prefix clientmod) (haskell-refac-renameAllIdentsIn2 f2 f2 f2prefix clientmod) ;; prepare the generative fold operations : ;; the equations for functions of interest are saved into comments (haskell-refac-duplicateTopLevelDefIntoComment f1 clientmod) (haskell-refac-duplicateTopLevelDefIntoComment f2 clientmod) ;; unfold the use of the traversal function ;; in the definition of functions of interest (haskell-refac-unfoldIn f1reducer f1 clientmod) (haskell-refac-unfoldIn f1reducer f2 clientmod) ;; fold the use of the traversal function in the body of the ;; functions of interest in order to find a recursive definition of them ;; (without a call to the traversal function) (haskell-refac-generativeFoldAllIdentAppIn f1 f1reducer clientmod) (haskell-refac-generativeFoldAllIdentAppIn f2 f1reducer clientmod) ;; comments introduced for the generative fold can be deleted (haskell-refac-rmCommentBeforeTopLevelDef f1 clientmod) (haskell-refac-rmCommentBeforeTopLevelDef f2 clientmod) ;; generative fold has produced case expressions that have to be simplified (haskell-refac-repeatSimplifyCasePatternIn f1 clientmod) (haskell-refac-repeatSimplifyCasePatternIn f2 clientmod) ;; the case expressions introduced by the generative fold ;; have to be transformed into equations (haskell-refac-caseToEqIn f1 clientmod) (haskell-refac-caseToEqIn f2 clientmod) ;; replace calls to the business functions by their bodies (unfold) (haskell-refac-forgetAllTopLevelIdentWithOccurenceIn f1 f1prefix clientmod) (haskell-refac-forgetAllTopLevelIdentWithOccurenceIn f2 f2prefix clientmod) ;; the traversal functions can be deleted (haskell-refac-removeTopLevelDef f1reducer "Expr") (haskell-refac-addImplicitImportUnsafe clientmod f2mod);; the order is important for the order of the imports directives (haskell-refac-addImplicitImportUnsafe clientmod f1mod) (haskell-refac-moveDefBetweenModules f2 clientmod f2mod) (haskell-refac-moveDefBetweenModules f1 clientmod f1mod) ;; business functions are not used an can be deleted ;; (imports, exports and declarations) (haskell-refac-cleanImportsMod clientmod)