module Fay.Types.ModulePath
( ModulePath (..)
, mkModulePath
, mkModulePaths
, mkModulePathFromQName
) where
import Fay.Compiler.QName
import qualified Fay.Exts as F
import Data.List
import Data.List.Split
import Language.Haskell.Exts
newtype ModulePath = ModulePath { ModulePath -> [String]
unModulePath :: [String] }
deriving (ModulePath -> ModulePath -> Bool
(ModulePath -> ModulePath -> Bool)
-> (ModulePath -> ModulePath -> Bool) -> Eq ModulePath
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModulePath -> ModulePath -> Bool
$c/= :: ModulePath -> ModulePath -> Bool
== :: ModulePath -> ModulePath -> Bool
$c== :: ModulePath -> ModulePath -> Bool
Eq, Eq ModulePath
Eq ModulePath
-> (ModulePath -> ModulePath -> Ordering)
-> (ModulePath -> ModulePath -> Bool)
-> (ModulePath -> ModulePath -> Bool)
-> (ModulePath -> ModulePath -> Bool)
-> (ModulePath -> ModulePath -> Bool)
-> (ModulePath -> ModulePath -> ModulePath)
-> (ModulePath -> ModulePath -> ModulePath)
-> Ord ModulePath
ModulePath -> ModulePath -> Bool
ModulePath -> ModulePath -> Ordering
ModulePath -> ModulePath -> ModulePath
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ModulePath -> ModulePath -> ModulePath
$cmin :: ModulePath -> ModulePath -> ModulePath
max :: ModulePath -> ModulePath -> ModulePath
$cmax :: ModulePath -> ModulePath -> ModulePath
>= :: ModulePath -> ModulePath -> Bool
$c>= :: ModulePath -> ModulePath -> Bool
> :: ModulePath -> ModulePath -> Bool
$c> :: ModulePath -> ModulePath -> Bool
<= :: ModulePath -> ModulePath -> Bool
$c<= :: ModulePath -> ModulePath -> Bool
< :: ModulePath -> ModulePath -> Bool
$c< :: ModulePath -> ModulePath -> Bool
compare :: ModulePath -> ModulePath -> Ordering
$ccompare :: ModulePath -> ModulePath -> Ordering
$cp1Ord :: Eq ModulePath
Ord, Int -> ModulePath -> ShowS
[ModulePath] -> ShowS
ModulePath -> String
(Int -> ModulePath -> ShowS)
-> (ModulePath -> String)
-> ([ModulePath] -> ShowS)
-> Show ModulePath
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModulePath] -> ShowS
$cshowList :: [ModulePath] -> ShowS
show :: ModulePath -> String
$cshow :: ModulePath -> String
showsPrec :: Int -> ModulePath -> ShowS
$cshowsPrec :: Int -> ModulePath -> ShowS
Show)
mkModulePath :: ModuleName a -> ModulePath
mkModulePath :: ModuleName a -> ModulePath
mkModulePath (ModuleName a
_ String
m) = [String] -> ModulePath
ModulePath ([String] -> ModulePath)
-> (String -> [String]) -> String -> ModulePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> [String]
forall a. Eq a => [a] -> [a] -> [[a]]
splitOn String
"." (String -> ModulePath) -> String -> ModulePath
forall a b. (a -> b) -> a -> b
$ String
m
mkModulePaths :: ModuleName a -> [ModulePath]
mkModulePaths :: ModuleName a -> [ModulePath]
mkModulePaths (ModuleName a
_ String
m) = ([String] -> ModulePath) -> [[String]] -> [ModulePath]
forall a b. (a -> b) -> [a] -> [b]
map [String] -> ModulePath
ModulePath ([[String]] -> [ModulePath])
-> (String -> [[String]]) -> String -> [ModulePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[String]] -> [[String]]
forall a. [a] -> [a]
tail ([[String]] -> [[String]])
-> (String -> [[String]]) -> String -> [[String]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [[String]]
forall a. [a] -> [[a]]
inits ([String] -> [[String]])
-> (String -> [String]) -> String -> [[String]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> [String]
forall a. Eq a => [a] -> [a] -> [[a]]
splitOn String
"." (String -> [ModulePath]) -> String -> [ModulePath]
forall a b. (a -> b) -> a -> b
$ String
m
mkModulePathFromQName :: QName a -> ModulePath
mkModulePathFromQName :: QName a -> ModulePath
mkModulePathFromQName (Qual a
_ (ModuleName a
_ String
m) Name a
n) = ModuleName SrcSpanInfo -> ModulePath
forall a. ModuleName a -> ModulePath
mkModulePath (ModuleName SrcSpanInfo -> ModulePath)
-> ModuleName SrcSpanInfo -> ModulePath
forall a b. (a -> b) -> a -> b
$ SrcSpanInfo -> String -> ModuleName SrcSpanInfo
forall l. l -> String -> ModuleName l
ModuleName SrcSpanInfo
F.noI (String -> ModuleName SrcSpanInfo)
-> String -> ModuleName SrcSpanInfo
forall a b. (a -> b) -> a -> b
$ String
m String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"." String -> ShowS
forall a. [a] -> [a] -> [a]
++ Name a -> String
forall a. Name a -> String
unname Name a
n
mkModulePathFromQName QName a
_ = String -> ModulePath
forall a. HasCallStack => String -> a
error String
"mkModulePathFromQName: Not a qualified name"