hsc3-rw-0.14: hsc3 re-writing

Safe HaskellSafe-Inferred

Sound.SC3.RW.HP

Contents

Description

Hash parentheses. A simple minded haskell pre-processor that extends the haskell do syntax by rewriting # parenthesised elements of a right hand side expression as monadic bindings. The basic pre-processor is hp_rewrite.

Synopsis

String

indent_of :: String -> StringSource

Return indentation of line.

 indent_of "  a <- b" == "  "

remove_indent :: String -> StringSource

Delete indentation of line.

 remove_indent "  a <- b"  == "a <- b"

List

split_on_1 :: Eq a => [a] -> [a] -> Maybe ([a], [a])Source

Variant of splitOn requiring one match only.

 split_on_1 " <- " "  a <- f #(b) #(c)" == Just ("  a","f #(b) #(c)")
 split_on_1 " do " "  let a = do f #(b) #(c)" == Just ("  let a =","f #(b) #(c)")

Inline do

hp_remove_inline_do :: String -> [String]Source

Split inline do line into separate lines.

 let r = ["  let a = do "
         ,"             f #(b) #(c)"]
 in hp_remove_inline_do "  let a = do f #(b) #(c)" == r

Continuation lines

hp_indent :: String -> Maybe IntSource

Return indent of s if it has_hash_paren.

 hp_indent "  a <- f #(b) #(c)" == Just 2

hp_non_inline :: [String] -> [Bool]Source

Note which lines are continued hash parenethsis lines.

 hp_non_inline ["f = do"
               ,"  a #(b)"
               ,"    #(c)"
               ,"    #(d)"
               ,"  p #(q) #(r)"] == [False,False,True,True,False]

hp_uncontinue :: [String] -> [String]Source

Re-layout to put broken hash parenthesis lines onto one line.

 let r = ["f = do"
         ,"  a #(b) #(c) #(d)"
         ,"  p #(q) #(r)"]
 in hp_uncontinue ["f = do"
                  ,"  a #(b)"
                  ,"    #(c)"
                  ,"    #(d)"
                  ,"  p #(q) #(r)"] == r

Hash Parentheses

hp_names :: Name_SupplySource

Name supply for introduced variables.

 hp_names !! 9 == "_hp_9"

has_hash_paren :: String -> BoolSource

Does s have a hash parenthesis expression.

 has_hash_paren "  a <- f #(b) #(c)" == True

hp_analyse :: Name_Supply -> String -> (Name_Supply, ([Binding], HP))Source

Process one line of hash-parenthesis re-writes.

hp_analyse' :: Name_Supply -> String -> ([Binding], String)Source

Variant of hp_analyse for examining intermediate state.

 let r = ([("_hp_0","b"),("_hp_1","c (d e)")],"  a <- f _hp_0 _hp_1")
 in hp_analyse' hp_names "  a <- f #(b) #(c (d e))" == r
 let r = ([("_hp_0","a")],"  return (f _hp_0)")
 in hp_analyse' hp_names "  return (f #(a))" == r
 let r = ([("_hp_0","a"),("_hp_1","d e"),("_hp_2","c _hp_1 f"),("_hp_3","b _hp_2 g")]
         ,"c <- f (_hp_0,_hp_3) h")
 in hp_analyse' hp_names "c <- f (#(a),#(b #(c #(d e) f) g)) h" == r
 let r = ([("_hp_0","v w")],"  return (h (_hp_0 * 2))")
 in hp_analyse' hp_names "  return (h (#(v w) * 2))" == r

hp_build :: ([Binding], HP) -> [String]Source

Re-construct hp_analyse output.

hp_process :: Name_Supply -> String -> (Name_Supply, [String])Source

Process a line for hash parentheses.

hp_rewrite :: [String] -> [String]Source

Run hash parenthesis rewriter.

 let {i = ["main = do"
          ,"  let a = f #(b) (#(c) * 2)"
          ,"  d <- e"
          ,"  p <- g #(q r)"
          ,"         #(s #(t u))"
          ,"  return (h (#(v w) * 2))"]
     ;r = ["main = do"
          ,"  _hp_0 <- b"
          ,"  _hp_1 <- c"
          ,"  let a = f _hp_0 (_hp_1 * 2)"
          ,"  d <- e"
          ,"  _hp_2 <- q r"
          ,"  _hp_3 <- t u"
          ,"  _hp_4 <- s _hp_3"
          ,"  p <- g _hp_2 _hp_4"
          ,"  _hp_5 <- v w"
          ,"  return (h (_hp_5 * 2))"]}
 in hp_rewrite i == r

hp_rewrite_ghcF :: IO ()Source

Arguments as required by ghc -F -pgmF.