module Camfort.Helpers where
import Data.List (elemIndices, group, sort, nub)
import qualified Data.ByteString.Char8 as B
import System.Directory
import Language.Fortran
lineCol :: SrcLoc -> (Int, Int)
lineCol s = (srcLine s, srcColumn s)
spanLineCol :: SrcSpan -> ((Int, Int), (Int, Int))
spanLineCol (l, u) = (lineCol l, lineCol u)
type Filename = String
type Directory = String
type SourceText = B.ByteString
type FileOrDir = String
getDir :: String -> String
getDir file = let ixs = elemIndices '/' file
in if null ixs then file
else take (last $ ixs) file
checkDir f = case (elemIndices '/' f) of
[] -> return ()
ix -> let d = take (last ix) f
in createDirectoryIfMissing True d
isDirectory :: FileOrDir -> IO Bool
isDirectory s = doesDirectoryExist s
fanout :: (a -> b) -> (a -> c) -> a -> (b, c)
fanout f g x = (f x, g x)
(<>) :: (a -> b) -> (a -> c) -> a -> (b, c)
f <> g = fanout f g
(><) :: (a -> c) -> (b -> d) -> (a, b) -> (c, d)
f >< g = \(x, y) -> (f x, g y)
lookups :: Eq a => a -> [(a, b)] -> [b]
lookups _ [] = []
lookups x ((a, b):xs) = if (x == a) then b : lookups x xs
else lookups x xs
lookups' :: Eq a => a -> [((a, b), c)] -> [(b, c)]
lookups' _ [] = []
lookups' x (((a, b), c):xs) = if (x == a) then (b, c) : lookups' x xs
else lookups' x xs
pairs :: [a] -> [(a, a)]
pairs [] = []
pairs (x:xs) = (zip (repeat x) xs) ++ (pairs xs)
mfmap :: Functor f => (a -> b) -> [f a] -> [f b]
mfmap f = map (fmap f)
each = flip (map)
cmpEq :: Ordering -> Bool
cmpEq EQ = True
cmpEq _ = False
cmpFst :: (a -> a -> Ordering) -> (a, b) -> (a, b) -> Ordering
cmpFst c (x1, y1) (x2, y2) = c x1 x2
cmpSnd :: (b -> b -> Ordering) -> (a, b) -> (a, b) -> Ordering
cmpSnd c (x1, y1) (x2, y2) = c y1 y2
type (:?) a (b :: k) = a
foldPair :: (a -> a -> Maybe a) -> [a] -> [a]
foldPair f [] = []
foldPair f [a] = [a]
foldPair f (a:(b:xs)) = case f a b of
Nothing -> a : (foldPair f (b : xs))
Just c -> foldPair f (c : xs)
class PartialMonoid x where
emptyM :: x
appendM :: x -> x -> Maybe x
normalise :: (Ord t, PartialMonoid t) => [t] -> [t]
normalise = nub . reduce . sort
where reduce = foldPair appendM
normaliseNoSort :: (Ord t, PartialMonoid t) => [t] -> [t]
normaliseNoSort = nub . reduce
where reduce = foldPair appendM
normaliseBy :: Ord t => (t -> t -> Maybe t) -> [t] -> [t]
normaliseBy plus = nub . (foldPair plus) . sort