diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/FS.purs | 45 | ||||
-rw-r--r-- | src/Glob.purs | 31 | ||||
-rw-r--r-- | src/Loader.purs | 102 | ||||
-rw-r--r-- | src/LoaderRef.purs | 25 | ||||
-rw-r--r-- | src/OS.purs | 3 | ||||
-rw-r--r-- | src/Options.purs | 46 | ||||
-rw-r--r-- | src/Path.purs | 36 |
7 files changed, 42 insertions, 246 deletions
diff --git a/src/FS.purs b/src/FS.purs deleted file mode 100644 index 68fe2f9..0000000 --- a/src/FS.purs +++ /dev/null | |||
@@ -1,45 +0,0 @@ | |||
1 | module PursLoader.FS | ||
2 | ( FS() | ||
3 | , readFileUtf8 | ||
4 | , readFileUtf8Sync | ||
5 | ) where | ||
6 | |||
7 | import Control.Monad.Aff (Aff(), makeAff) | ||
8 | import Control.Monad.Eff (Eff()) | ||
9 | import Control.Monad.Eff.Exception (Error()) | ||
10 | |||
11 | import Data.Function | ||
12 | |||
13 | foreign import data FS :: ! | ||
14 | |||
15 | readFileUtf8 :: forall eff. String -> Aff (fs :: FS | eff) String | ||
16 | readFileUtf8 filepath = makeAff $ runFn3 readFileUtf8Fn filepath | ||
17 | |||
18 | readFileUtf8Sync :: forall eff. String -> Eff (fs :: FS | eff) String | ||
19 | readFileUtf8Sync filepath = readFileUtf8SyncFn filepath | ||
20 | |||
21 | foreign import readFileUtf8Fn """ | ||
22 | function readFileUtf8Fn(filepath, errback, callback) { | ||
23 | return function(){ | ||
24 | var fs = require('fs'); | ||
25 | |||
26 | fs.readFile(filepath, 'utf-8', function(e, data){ | ||
27 | if (e) errback(e)(); | ||
28 | else callback(data)(); | ||
29 | }); | ||
30 | }; | ||
31 | } | ||
32 | """ :: forall eff. Fn3 String | ||
33 | (Error -> Eff (fs :: FS | eff) Unit) | ||
34 | (String -> Eff (fs :: FS | eff) Unit) | ||
35 | (Eff (fs :: FS | eff) Unit) | ||
36 | |||
37 | foreign import readFileUtf8SyncFn """ | ||
38 | function readFileUtf8SyncFn(filepath) { | ||
39 | return function(){ | ||
40 | var fs = require('fs'); | ||
41 | |||
42 | return fs.readFileSync(filepath, {encoding: 'utf-8'}); | ||
43 | }; | ||
44 | } | ||
45 | """ :: forall eff. String -> (Eff (fs :: FS | eff) String) | ||
diff --git a/src/Glob.purs b/src/Glob.purs deleted file mode 100644 index 7bc9212..0000000 --- a/src/Glob.purs +++ /dev/null | |||
@@ -1,31 +0,0 @@ | |||
1 | module PursLoader.Glob | ||
2 | ( Glob() | ||
3 | , glob | ||
4 | ) where | ||
5 | |||
6 | import Control.Monad.Aff (Aff(), makeAff) | ||
7 | import Control.Monad.Eff (Eff()) | ||
8 | import Control.Monad.Eff.Exception (Error()) | ||
9 | |||
10 | import Data.Function | ||
11 | |||
12 | foreign import data Glob :: ! | ||
13 | |||
14 | glob :: forall eff. String -> Aff (glob :: Glob | eff) [String] | ||
15 | glob pattern = makeAff $ runFn3 globFn pattern | ||
16 | |||
17 | foreign import globFn """ | ||
18 | function globFn(pattern, errback, callback) { | ||
19 | return function(){ | ||
20 | var glob = require('glob'); | ||
21 | |||
22 | glob(pattern, function(e, data){ | ||
23 | if (e) errback(e)(); | ||
24 | else callback(data)(); | ||
25 | }); | ||
26 | }; | ||
27 | } | ||
28 | """ :: forall eff. Fn3 String | ||
29 | (Error -> Eff (glob :: Glob | eff) Unit) | ||
30 | ([String] -> Eff (glob :: Glob | eff) Unit) | ||
31 | (Eff (glob :: Glob | eff) Unit) | ||
diff --git a/src/Loader.purs b/src/Loader.purs index fedc424..0235da9 100644 --- a/src/Loader.purs +++ b/src/Loader.purs | |||
@@ -1,5 +1,5 @@ | |||
1 | module PursLoader.Loader | 1 | module PursLoader.Loader |
2 | ( LoaderEff() | 2 | ( Effects() |
3 | , loader | 3 | , loader |
4 | , loaderFn | 4 | , loaderFn |
5 | ) where | 5 | ) where |
@@ -9,113 +9,45 @@ import Control.Monad.Eff (Eff()) | |||
9 | import Control.Monad.Eff.Class (liftEff) | 9 | import Control.Monad.Eff.Class (liftEff) |
10 | import Control.Monad.Eff.Exception (error) | 10 | import Control.Monad.Eff.Exception (error) |
11 | 11 | ||
12 | import Data.Array ((!!), catMaybes, concat, filter, null) | 12 | import Data.Array ((!!)) |
13 | import Data.Foldable (foldl) | ||
14 | import Data.Function (Fn2(), mkFn2) | 13 | import Data.Function (Fn2(), mkFn2) |
15 | import Data.Maybe (Maybe(..), fromMaybe, maybe) | 14 | import Data.Maybe (Maybe(..), fromMaybe, maybe) |
16 | import Data.Set (Set(), empty, insert, member, toList, unions) | 15 | import Data.String.Regex (match, noFlags, regex) |
17 | import Data.String (joinWith, split) | ||
18 | import Data.String.Regex (Regex(), match, noFlags, regex) | ||
19 | import Data.StrMap (StrMap(), fromList, lookup) | ||
20 | import Data.Traversable (sequence) | ||
21 | import Data.Tuple.Nested (tuple2) | ||
22 | 16 | ||
23 | import PursLoader.ChildProcess (ChildProcess(), spawn) | 17 | import PursLoader.ChildProcess (ChildProcess(), spawn) |
24 | import PursLoader.FS (FS(), readFileUtf8, readFileUtf8Sync) | 18 | import PursLoader.LoaderRef (LoaderRef(), Loader(), async, cacheable, query) |
25 | import PursLoader.Glob (Glob(), glob) | ||
26 | import PursLoader.LoaderRef (LoaderRef(), Loader(), async, cacheable, clearDependencies, addDependency, query, resourcePath) | ||
27 | import PursLoader.LoaderUtil (getRemainingRequest, parseQuery) | 19 | import PursLoader.LoaderUtil (getRemainingRequest, parseQuery) |
28 | import PursLoader.OS (eol) | 20 | import PursLoader.Options (loaderSrcOption, pscOptions) |
29 | import PursLoader.Options (loaderSrcOption, pscMakeOptions, pscMakeDefaultOutput, pscMakeOutputOption) | ||
30 | import PursLoader.Path (dirname, join, relative, resolve) | ||
31 | 21 | ||
32 | foreign import cwd "var cwd = process.cwd();" :: String | 22 | type Effects eff = (loader :: Loader, cp :: ChildProcess | eff) |
33 | 23 | ||
34 | moduleRegex = regex "(?:^|\\n)module\\s+([\\w\\.]+)" noFlags { ignoreCase = true } | 24 | moduleRegex = regex "(?:^|\\n)module\\s+([\\w\\.]+)" noFlags { ignoreCase = true } |
35 | 25 | ||
36 | importRegex = regex "^\\s*import\\s+(?:qualified\\s+)?([\\w\\.]+)" noFlags { ignoreCase = true } | 26 | pscCommand = "psc" |
37 | |||
38 | bowerPattern = join [ "bower_components", "purescript-*", "src" ] | ||
39 | |||
40 | pscMakeCommand = "psc-make" | ||
41 | |||
42 | indexFilename = "index.js" | ||
43 | 27 | ||
44 | (!!!) = flip (!!) | 28 | (!!!) = flip (!!) |
45 | 29 | ||
46 | pursPattern :: [String] -> String | 30 | loader' :: forall eff. LoaderRef -> String -> Aff (Effects eff) (Maybe String) |
47 | pursPattern srcs = join [ "{" ++ joinWith "," ([ bowerPattern ] <> srcs) ++ "}" | ||
48 | , "**" | ||
49 | , "*.purs" | ||
50 | ] | ||
51 | |||
52 | type GraphModule = { file :: String, imports :: [String] } | ||
53 | |||
54 | type Graph = StrMap GraphModule | ||
55 | |||
56 | mkGraph :: forall eff. [String] -> Eff (fs :: FS | eff) Graph | ||
57 | mkGraph files = (fromList <<< catMaybes) <$> sequence (parse <$> files) | ||
58 | where parse file = do source <- readFileUtf8Sync file | ||
59 | let key = match moduleRegex source >>= (!!!) 1 | ||
60 | lines = split eol source | ||
61 | imports = catMaybes $ (\a -> match importRegex a >>= (!!!) 1) <$> lines | ||
62 | return $ (\a -> tuple2 a { file: file, imports: imports }) <$> key | ||
63 | |||
64 | mkDeps :: forall eff. String -> Graph -> [String] | ||
65 | mkDeps key graph = toList $ go empty key | ||
66 | where | ||
67 | go :: Set String -> String -> Set String | ||
68 | go acc key = | ||
69 | let node = fromMaybe {file: "", imports: []} (lookup key graph) | ||
70 | uniq = filter (not <<< flip member acc) node.imports | ||
71 | acc' = foldl (flip insert) acc node.imports | ||
72 | in if null uniq | ||
73 | then acc' | ||
74 | else unions $ go acc' <$> uniq | ||
75 | |||
76 | addDeps :: forall eff. LoaderRef -> Graph -> [String] -> Eff (loader :: Loader | eff) Unit | ||
77 | addDeps ref graph deps = const unit <$> (sequence $ add <$> deps) | ||
78 | where add dep = let res = lookup dep graph | ||
79 | path = (\a -> resolve a.file) <$> res | ||
80 | in maybe (pure unit) (addDependency ref) path | ||
81 | |||
82 | type LoaderAff eff a = Aff (loader :: Loader, glob :: Glob, cp :: ChildProcess, fs :: FS | eff) a | ||
83 | |||
84 | loader' :: forall eff. LoaderRef -> String -> LoaderAff eff (Maybe String) | ||
85 | loader' ref source = do | 31 | loader' ref source = do |
86 | liftEff $ cacheable ref | 32 | liftEff $ cacheable ref |
87 | 33 | ||
88 | let request = getRemainingRequest ref | 34 | let request = getRemainingRequest ref |
89 | parsed = parseQuery $ query ref | 35 | parsed = parseQuery $ query ref |
90 | srcs = loaderSrcOption parsed | 36 | srcs = fromMaybe [] (loaderSrcOption parsed) |
91 | opts = pscMakeOptions parsed | 37 | opts = pscOptions parsed |
92 | pattern = pursPattern $ fromMaybe [] srcs | 38 | moduleName = match moduleRegex source >>= (!!!) 1 |
93 | key = match moduleRegex source >>= (!!!) 1 | 39 | result = (\a -> "module.exports = require('" ++ a ++ "');") <$> moduleName |
94 | |||
95 | files <- glob pattern | ||
96 | graph <- liftEff $ mkGraph files | ||
97 | |||
98 | let deps = fromMaybe [] $ flip mkDeps graph <$> key | ||
99 | outputPath = fromMaybe pscMakeDefaultOutput $ pscMakeOutputOption parsed | ||
100 | indexPath = (\a -> join [ outputPath, a, indexFilename ]) <$> key | ||
101 | |||
102 | liftEff $ clearDependencies ref | ||
103 | liftEff $ addDependency ref (resourcePath ref) | ||
104 | liftEff $ addDeps ref graph deps | ||
105 | |||
106 | spawn pscMakeCommand (opts <> files) | ||
107 | indexFile <- sequence $ readFileUtf8 <$> indexPath | ||
108 | return indexFile | ||
109 | 40 | ||
110 | type LoaderEff eff a = Eff (loader :: Loader, glob :: Glob, cp :: ChildProcess, fs :: FS | eff) a | 41 | spawn pscCommand (srcs <> opts) |
42 | return result | ||
111 | 43 | ||
112 | loader :: forall eff. LoaderRef -> String -> LoaderEff eff Unit | 44 | loader :: forall eff. LoaderRef -> String -> Eff (Effects eff) Unit |
113 | loader ref source = do | 45 | loader ref source = do |
114 | callback <- async ref | 46 | callback <- async ref |
115 | runAff (\e -> callback (Just e) "") | 47 | runAff (\e -> callback (Just e) "") |
116 | (maybe (callback (Just $ error "Loader has failed to run") "") | 48 | (maybe (callback (Just (error "Loader has failed to run")) "") |
117 | (callback Nothing)) | 49 | (callback Nothing)) |
118 | (loader' ref source) | 50 | (loader' ref source) |
119 | 51 | ||
120 | loaderFn :: forall eff. Fn2 LoaderRef String (LoaderEff eff Unit) | 52 | loaderFn :: forall eff. Fn2 LoaderRef String (Eff (Effects eff) Unit) |
121 | loaderFn = mkFn2 loader | 53 | loaderFn = mkFn2 loader |
diff --git a/src/LoaderRef.purs b/src/LoaderRef.purs index 2d62754..2567b1e 100644 --- a/src/LoaderRef.purs +++ b/src/LoaderRef.purs | |||
@@ -3,16 +3,12 @@ module PursLoader.LoaderRef | |||
3 | , Loader() | 3 | , Loader() |
4 | , async | 4 | , async |
5 | , cacheable | 5 | , cacheable |
6 | , clearDependencies | ||
7 | , resourcePath | ||
8 | , addDependency | ||
9 | , query | 6 | , query |
10 | ) where | 7 | ) where |
11 | 8 | ||
12 | import Control.Monad.Eff (Eff()) | 9 | import Control.Monad.Eff (Eff()) |
13 | import Control.Monad.Eff.Exception (Error()) | 10 | import Control.Monad.Eff.Exception (Error()) |
14 | 11 | ||
15 | import Data.Foreign (Foreign()) | ||
16 | import Data.Function (Fn3(), runFn3) | 12 | import Data.Function (Fn3(), runFn3) |
17 | import Data.Maybe (Maybe(), fromMaybe, isJust) | 13 | import Data.Maybe (Maybe(), fromMaybe, isJust) |
18 | 14 | ||
@@ -48,27 +44,6 @@ function cacheable(ref){ | |||
48 | }; | 44 | }; |
49 | }""" :: forall eff. LoaderRef -> Eff (loader :: Loader | eff) Unit | 45 | }""" :: forall eff. LoaderRef -> Eff (loader :: Loader | eff) Unit |
50 | 46 | ||
51 | foreign import clearDependencies """ | ||
52 | function clearDependencies(ref){ | ||
53 | return function(){ | ||
54 | return ref.clearDependencies(); | ||
55 | }; | ||
56 | }""" :: forall eff. LoaderRef -> Eff (loader :: Loader | eff) Unit | ||
57 | |||
58 | foreign import resourcePath """ | ||
59 | function resourcePath(ref){ | ||
60 | return ref.resourcePath; | ||
61 | }""" :: LoaderRef -> String | ||
62 | |||
63 | foreign import addDependency """ | ||
64 | function addDependency(ref){ | ||
65 | return function(dep){ | ||
66 | return function(){ | ||
67 | return ref.addDependency(dep); | ||
68 | }; | ||
69 | }; | ||
70 | }""" :: forall eff. LoaderRef -> String -> Eff (loader :: Loader | eff) Unit | ||
71 | |||
72 | foreign import query """ | 47 | foreign import query """ |
73 | function query(ref){ | 48 | function query(ref){ |
74 | return ref.query; | 49 | return ref.query; |
diff --git a/src/OS.purs b/src/OS.purs deleted file mode 100644 index 590c3d6..0000000 --- a/src/OS.purs +++ /dev/null | |||
@@ -1,3 +0,0 @@ | |||
1 | module PursLoader.OS (eol) where | ||
2 | |||
3 | foreign import eol "var eol = require('os').EOL;" :: String | ||
diff --git a/src/Options.purs b/src/Options.purs index c47bebc..be21877 100644 --- a/src/Options.purs +++ b/src/Options.purs | |||
@@ -1,17 +1,16 @@ | |||
1 | module PursLoader.Options | 1 | module PursLoader.Options |
2 | ( pscMakeOptions | 2 | ( pscOptions |
3 | , pscMakeDefaultOutput | ||
4 | , pscMakeOutputOption | ||
5 | , loaderSrcOption | 3 | , loaderSrcOption |
6 | ) where | 4 | ) where |
7 | 5 | ||
6 | import Data.Array (concat) | ||
8 | import Data.Either (either) | 7 | import Data.Either (either) |
9 | 8 | ||
10 | import Data.Foreign (Foreign(), F()) | 9 | import Data.Foreign (Foreign(), F()) |
11 | import Data.Foreign.Class (IsForeign, read, readProp) | 10 | import Data.Foreign.Class (IsForeign, read, readProp) |
12 | import Data.Foreign.NullOrUndefined (NullOrUndefined(), runNullOrUndefined) | 11 | import Data.Foreign.NullOrUndefined (NullOrUndefined(..), runNullOrUndefined) |
13 | 12 | ||
14 | import Data.Maybe (Maybe(..), maybe) | 13 | import Data.Maybe (Maybe(..), maybe, fromMaybe) |
15 | 14 | ||
16 | noPreludeOpt = "no-prelude" | 15 | noPreludeOpt = "no-prelude" |
17 | 16 | ||
@@ -29,9 +28,11 @@ commentsOpt = "comments" | |||
29 | 28 | ||
30 | noPrefixOpt = "no-prefix" | 29 | noPrefixOpt = "no-prefix" |
31 | 30 | ||
31 | requirePathOpt = "require-path" | ||
32 | |||
32 | srcOpt = "src" | 33 | srcOpt = "src" |
33 | 34 | ||
34 | pscMakeDefaultOutput = "output" | 35 | ffiOpt = "ffi" |
35 | 36 | ||
36 | newtype Options | 37 | newtype Options |
37 | = Options { noPrelude :: NullOrUndefined Boolean | 38 | = Options { noPrelude :: NullOrUndefined Boolean |
@@ -42,7 +43,9 @@ newtype Options | |||
42 | , comments :: NullOrUndefined Boolean | 43 | , comments :: NullOrUndefined Boolean |
43 | , output :: NullOrUndefined String | 44 | , output :: NullOrUndefined String |
44 | , noPrefix :: NullOrUndefined Boolean | 45 | , noPrefix :: NullOrUndefined Boolean |
46 | , requirePath :: NullOrUndefined String | ||
45 | , src :: NullOrUndefined [String] | 47 | , src :: NullOrUndefined [String] |
48 | , ffi :: NullOrUndefined [String] | ||
46 | } | 49 | } |
47 | 50 | ||
48 | instance isForeignOptions :: IsForeign Options where | 51 | instance isForeignOptions :: IsForeign Options where |
@@ -54,7 +57,9 @@ instance isForeignOptions :: IsForeign Options where | |||
54 | , comments: _ | 57 | , comments: _ |
55 | , output: _ | 58 | , output: _ |
56 | , noPrefix: _ | 59 | , noPrefix: _ |
60 | , requirePath: _ | ||
57 | , src: _ | 61 | , src: _ |
62 | , ffi: _ | ||
58 | } <$> readProp noPreludeOpt obj | 63 | } <$> readProp noPreludeOpt obj |
59 | <*> readProp noOptsOpt obj | 64 | <*> readProp noOptsOpt obj |
60 | <*> readProp noMagicDoOpt obj | 65 | <*> readProp noMagicDoOpt obj |
@@ -63,26 +68,25 @@ instance isForeignOptions :: IsForeign Options where | |||
63 | <*> readProp commentsOpt obj | 68 | <*> readProp commentsOpt obj |
64 | <*> readProp outputOpt obj | 69 | <*> readProp outputOpt obj |
65 | <*> readProp noPrefixOpt obj | 70 | <*> readProp noPrefixOpt obj |
66 | <*> readProp srcOpt obj) | 71 | <*> readProp requirePathOpt obj |
72 | <*> readProp srcOpt obj | ||
73 | <*> readProp ffiOpt obj) | ||
67 | 74 | ||
68 | class LoaderOption a where | 75 | class LoaderOption a where |
69 | opt :: String -> NullOrUndefined a -> [String] | 76 | opt :: String -> NullOrUndefined a -> [String] |
70 | 77 | ||
71 | instance booleanLoaderOption :: LoaderOption Boolean where | 78 | instance booleanLoaderOption :: LoaderOption Boolean where |
72 | opt key opt = maybe [] (\a -> if a then ["--" ++ key] else []) | 79 | opt key val = maybe [] (\a -> if a then ["--" ++ key] else []) (runNullOrUndefined val) |
73 | (runNullOrUndefined opt) | ||
74 | 80 | ||
75 | instance stringLoaderOption :: LoaderOption String where | 81 | instance stringLoaderOption :: LoaderOption String where |
76 | opt key opt = maybe [] (\a -> ["--" ++ key ++ "=" ++ a]) | 82 | opt key val = maybe [] (\a -> ["--" ++ key ++ "=" ++ a]) (runNullOrUndefined val) |
77 | (runNullOrUndefined opt) | ||
78 | 83 | ||
79 | pscMakeOutputOption :: Foreign -> Maybe String | 84 | instance arrayLoaderOption :: (LoaderOption a) => LoaderOption [a] where |
80 | pscMakeOutputOption query = either (const Nothing) | 85 | opt key val = concat (opt key <$> (NullOrUndefined <<< Just) |
81 | (\(Options a) -> runNullOrUndefined a.output) | 86 | <$> (fromMaybe [] (runNullOrUndefined val))) |
82 | (read query) | ||
83 | 87 | ||
84 | pscMakeOptions :: Foreign -> [String] | 88 | pscOptions :: Foreign -> [String] |
85 | pscMakeOptions query = either (const []) fold parsed | 89 | pscOptions query = either (const []) fold parsed |
86 | where parsed = read query :: F Options | 90 | where parsed = read query :: F Options |
87 | fold (Options a) = opt noPreludeOpt a.noPrelude <> | 91 | fold (Options a) = opt noPreludeOpt a.noPrelude <> |
88 | opt noOptsOpt a.noOpts <> | 92 | opt noOptsOpt a.noOpts <> |
@@ -91,9 +95,9 @@ pscMakeOptions query = either (const []) fold parsed | |||
91 | opt verboseErrorsOpt a.verboseErrors <> | 95 | opt verboseErrorsOpt a.verboseErrors <> |
92 | opt commentsOpt a.comments <> | 96 | opt commentsOpt a.comments <> |
93 | opt outputOpt a.output <> | 97 | opt outputOpt a.output <> |
94 | opt noPrefixOpt a.noPrefix | 98 | opt noPrefixOpt a.noPrefix <> |
99 | opt requirePathOpt a.requirePath <> | ||
100 | opt ffiOpt a.ffi | ||
95 | 101 | ||
96 | loaderSrcOption :: Foreign -> Maybe [String] | 102 | loaderSrcOption :: Foreign -> Maybe [String] |
97 | loaderSrcOption query = either (const Nothing) | 103 | loaderSrcOption query = either (const Nothing) (\(Options a) -> runNullOrUndefined a.src) (read query) |
98 | (\(Options a) -> runNullOrUndefined a.src) | ||
99 | (read query) | ||
diff --git a/src/Path.purs b/src/Path.purs deleted file mode 100644 index e071e35..0000000 --- a/src/Path.purs +++ /dev/null | |||
@@ -1,36 +0,0 @@ | |||
1 | module PursLoader.Path | ||
2 | ( dirname | ||
3 | , join | ||
4 | , relative | ||
5 | , resolve | ||
6 | ) where | ||
7 | |||
8 | foreign import dirname """ | ||
9 | function dirname(filepath) { | ||
10 | var path = require('path'); | ||
11 | return path.dirname(filepath); | ||
12 | } | ||
13 | """ :: String -> String | ||
14 | |||
15 | foreign import join """ | ||
16 | function join(parts) { | ||
17 | var path = require('path'); | ||
18 | return path.join.apply(path, parts); | ||
19 | } | ||
20 | """ :: [String] -> String | ||
21 | |||
22 | foreign import relative """ | ||
23 | function relative(from) { | ||
24 | return function(to){ | ||
25 | var path = require('path'); | ||
26 | return path.relative(from, to); | ||
27 | }; | ||
28 | } | ||
29 | """ :: String -> String -> String | ||
30 | |||
31 | foreign import resolve """ | ||
32 | function resolve(filepath) { | ||
33 | var path = require('path'); | ||
34 | return path.resolve(filepath); | ||
35 | } | ||
36 | """ :: String -> String | ||