
The occam parser is now a GenParser Token OccState, rather than a GenParser Char OccState, and a lot of now-redundant code has been removed. The parser is also somewhat faster, which wasn't intended but is nice anyway. I've also modified the Rain parser to not rely on the old preprocessing code; it wasn't appropriate for Rain's syntax anyway, so I assume Neil will be replacing it eventually.
73 lines
2.4 KiB
Haskell
73 lines
2.4 KiB
Haskell
{-
|
|
Tock: a compiler for parallel languages
|
|
Copyright (C) 2007 University of Kent
|
|
|
|
This program is free software; you can redistribute it and/or modify it
|
|
under the terms of the GNU General Public License as published by the
|
|
Free Software Foundation, either version 2 of the License, or (at your
|
|
option) any later version.
|
|
|
|
This program is distributed in the hope that it will be useful, but
|
|
WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
|
|
General Public License for more details.
|
|
|
|
You should have received a copy of the GNU General Public License along
|
|
with this program. If not, see <http://www.gnu.org/licenses/>.
|
|
-}
|
|
|
|
-- | Utility functions that aren't inherently related to Tock -- i.e. things
|
|
-- that could be put into the standard library.
|
|
module Utils where
|
|
|
|
import Control.Monad
|
|
import System.IO
|
|
import System.IO.Error
|
|
import Text.Regex
|
|
|
|
-- | Split the directory and file components of a path.
|
|
splitPath :: String -> (String, String)
|
|
splitPath path
|
|
= case matchRegex dirRE path of
|
|
Just [dir, base] -> (if dir == "" then "." else dir, base)
|
|
where
|
|
dirRE = mkRegex "^(.*/)?([^/]*)$"
|
|
|
|
-- | Return the directory containing a path.
|
|
dirnamePath :: String -> String
|
|
dirnamePath = fst . splitPath
|
|
|
|
-- | Return a path without any leading directory components.
|
|
basenamePath :: String -> String
|
|
basenamePath = snd . splitPath
|
|
|
|
-- | Join a relative path to an existing path (i.e. if you're given foo/bar and
|
|
-- baz, return foo/baz).
|
|
joinPath :: String -> String -> String
|
|
joinPath base new
|
|
= case dirnamePath base of
|
|
"." -> new
|
|
dir -> dir ++ new
|
|
|
|
-- | Given a monadic action wrapped in a `Maybe`, run it if there's one there;
|
|
-- if it's `Nothing`, then do nothing.
|
|
doMaybe :: Monad m => Maybe (m ()) -> m ()
|
|
doMaybe (Just a) = a
|
|
doMaybe Nothing = return ()
|
|
|
|
-- | Transforms between two `Either` types using the appropriate convert
|
|
-- function:
|
|
transformEither :: (a -> c) -> (b -> d) -> Either a b -> Either c d
|
|
transformEither funcLeft funcRight x = case x of
|
|
Left l -> Left (funcLeft l)
|
|
Right r -> Right (funcRight r)
|
|
|
|
-- | Try an IO operation, returning `Nothing` if it fails.
|
|
maybeIO :: IO a -> IO (Maybe a)
|
|
maybeIO op = catch (op >>= (return . Just)) (\e -> return Nothing)
|
|
|
|
-- | Remove a number of items from the start and end of a list.
|
|
chop :: Int -> Int -> [a] -> [a]
|
|
chop start end s = drop start (take (length s - end) s)
|
|
|