-- | Hash at-sign.  A simple minded haskell pre-processor that extends
-- the haskell syntax by rewriting @#\@@ sequences with a string
-- indicating the line and column number of the occurence.  The basic
-- pre-processor is 'ha_rewrite'.
module Sound.SC3.RW.HA where

import System.Environment {- base -}

-- * Hash At-Sign

-- | Find next /hash-at/, if there is one.
--
-- > ha_split 0 "let o = sinOsc AR (rand #@ 220 440) 0 * 0.1"
ha_split :: Integer -> String -> (Integer, String, String)
ha_split =
    let recur r n s =
            case s of
              [] -> (n,reverse r,[])
              '#' : '@' : s' -> (n + 2,reverse r,s')
              c : s' -> recur (c : r) (n + 1) s'
    in recur []

-- | Generate replacement for /hash-at/ given line and column numbers.
--
-- > ha_insert 14 23 == "(hash \"14:21\")"
ha_insert :: Integer -> Integer -> String
ha_insert ln cn = concat ["(hash \"",show ln,":",show (cn - 2),"\")"]

-- | Process line given line number.
--
-- > putStrLn$ha_process_ln 1 "let o = sinOsc AR (rand #@ 220 440) (rand2 #@ pi) * 0.1"
ha_process_ln :: Integer -> String -> String
ha_process_ln ln =
    let recur cn s =
            case ha_split cn s of
              (_,_,[]) -> s
              (cn',pre,post) -> pre ++ ha_insert ln cn' ++ recur cn' post
    in recur 0

-- | Re-write lines, starting at @1@.
ha_rewrite :: [String] -> [String]
ha_rewrite = zipWith ha_process_ln [1..]

-- | Arguments as required by @ghc -F -pgmF@.
ha_rewrite_ghcF :: IO ()
ha_rewrite_ghcF = do
  a <- getArgs
  case a of
    [_,i_fn,o_fn] -> do
           i <- readFile i_fn
           let f = unlines . ha_rewrite . lines
           writeFile o_fn (f i)
    _ -> error "initial-file input-file output-file"