1 | 1 |
{-# LANGUAGE OverloadedStrings #-}
|
2 | 2 |
|
3 | |
module Collage.Commands.Splice (runSplice, findFragments) where
|
| 3 |
module Collage.Commands.Splice(runSplice) where
|
4 | 4 |
|
5 | 5 |
import Control.Monad (foldM)
|
6 | 6 |
import qualified Data.Map as M
|
7 | 7 |
import qualified Data.Text as T
|
8 | 8 |
import qualified Data.Text.Lazy as TL
|
9 | 9 |
import qualified Data.Text.Lazy.IO as TL
|
10 | |
import qualified System.Exit as Sys
|
11 | 10 |
import System.FilePath ((</>))
|
12 | 11 |
import qualified System.FilePath as Sys
|
13 | 12 |
|
14 | 13 |
import Collage.Config
|
15 | 14 |
import Collage.Opts
|
| 15 |
import Collage.Utils
|
16 | 16 |
|
17 | 17 |
findFragmentIdentifiers :: TL.Text -> [T.Text]
|
18 | 18 |
findFragmentIdentifiers t
|
|
21 | 21 |
, not (TL.null f) = TL.toStrict f : findFragmentIdentifiers rs'
|
22 | 22 |
| otherwise = []
|
23 | 23 |
|
| 24 |
newtype Fragment = Fragment [T.Text] deriving (Eq, Show)
|
| 25 |
|
24 | 26 |
toIdent :: T.Text -> TL.Text
|
25 | 27 |
toIdent = TL.fromStrict . T.cons '«' . flip T.snoc '»'
|
26 | 28 |
|
27 | |
findFragments :: FilePath -> T.Text -> [Source] -> Either String (IO TL.Text)
|
| 29 |
findFragments :: FilePath -> T.Text -> [Source] -> Either TL.Text (IO TL.Text)
|
28 | 30 |
findFragments root s sources = case (T.splitOn "/" s) of
|
29 | |
[] -> error "(should not happen)"
|
| 31 |
[] -> throw "Invalid empty fragment name!"
|
30 | 32 |
(x:rs) -> case [ src
|
31 | 33 |
| src@Source { sourceName = n } <- sources
|
32 | 34 |
, n == x
|
33 | 35 |
] of
|
34 | 36 |
[src] -> go src rs (sourceExpose src)
|
35 | |
[] -> Left ("Unable to find source named " ++ T.unpack x)
|
36 | |
_ -> Left ("Ambiguous source name: " ++ T.unpack x)
|
| 37 |
[] -> throw ("Unable to find source named " % stext) x
|
| 38 |
_ -> throw ("Ambiguous source name: " % stext) x
|
37 | 39 |
where
|
38 | |
go :: Source -> [T.Text] -> Expose -> Either String (IO TL.Text)
|
| 40 |
|
39 | 41 |
go q [] (ExposeFile path) =
|
40 | 42 |
return (TL.readFile (root </> sourceDir q </> path))
|
41 | 43 |
go _ [] ExposeSections{} =
|
42 | |
Left $ concat [ "Splice identifier «"
|
43 | |
, T.unpack s
|
44 | |
, "» matches a file with sections, but "
|
45 | |
, "does not specify a section!"
|
46 | |
]
|
| 44 |
throw ("Splice identifier «" % stext %
|
| 45 |
"» matches a file with sections") s
|
47 | 46 |
go _ [] NamedMap{} =
|
48 | |
Left $ concat [ "Splice identifier «"
|
49 | |
, T.unpack s
|
50 | |
, "» matches a map, but does not specify "
|
51 | |
, "a key!"
|
52 | |
]
|
| 47 |
throw ("Splice identifier «" % stext %
|
| 48 |
"» matches a map, but does not specify a key!") s
|
53 | 49 |
|
54 | 50 |
go q [section] (ExposeSections path) =
|
55 | 51 |
return (readSection (root </> sourceDir q </> path) section)
|
56 | 52 |
|
57 | 53 |
go _ (_:_) (ExposeSections path) =
|
58 | |
Left $ concat [ "Splice identifier «"
|
59 | |
, T.unpack s
|
60 | |
, "» indexes too far into the path "
|
61 | |
, path
|
62 | |
, "!"
|
63 | |
]
|
| 54 |
throw ("Splice identifier «" % stext %
|
| 55 |
"» indexes too far into the path " % string % "!")
|
| 56 |
s path
|
64 | 57 |
|
65 | 58 |
go _ (_:_) (ExposeFile path) =
|
66 | |
Left $ concat [ "Splice identifier «"
|
67 | |
, T.unpack s
|
68 | |
, "» indexes too far into the file "
|
69 | |
, path
|
70 | |
, "!"
|
71 | |
]
|
| 59 |
throw ("Splice identifier «" % stext %
|
| 60 |
"» indexes too far into the file " % string % "!")
|
| 61 |
s path
|
72 | 62 |
|
73 | 63 |
go q (k:rs) (NamedMap m)
|
74 | 64 |
| Just e <- M.lookup k m = go q rs e
|
75 | |
| otherwise = Left $ concat
|
76 | |
[ "Splice identifier «"
|
77 | |
, T.unpack s
|
78 | |
, "» references a key "
|
79 | |
, T.unpack k
|
80 | |
, " which cannot be found."
|
81 | |
]
|
| 65 |
| otherwise = throw
|
| 66 |
("Splice identifier «" % stext %
|
| 67 |
"» references a key " % stext %
|
| 68 |
" which cannot be found.") s k
|
82 | 69 |
|
83 | 70 |
doReplacements :: FilePath -> [Source] -> TL.Text -> IO TL.Text
|
84 | 71 |
doReplacements root e original =
|
|
86 | 73 |
where
|
87 | 74 |
doReplace file frag = do
|
88 | 75 |
new <- case findFragments root frag e of
|
89 | |
Left err -> Sys.die err
|
| 76 |
Left err -> cError err
|
90 | 77 |
Right x -> x
|
91 | 78 |
return (TL.replace (toIdent frag) new file)
|
92 | 79 |
|
|
94 | 81 |
readSection path f = do
|
95 | 82 |
contents <- TL.readFile path
|
96 | 83 |
case TL.breakOn (toIdent f) contents of
|
97 | |
(_, "") -> Sys.die $ unwords [ "Unable to find section"
|
98 | |
, show f
|
99 | |
, "in file"
|
100 | |
, path
|
101 | |
]
|
| 84 |
(_, "") -> cError (format ("Unable to find section " % shown %
|
| 85 |
" in file " % string) f path)
|
102 | 86 |
(_, rs) ->
|
103 | 87 |
let (_, skipLine) = TL.breakOn "\n" rs
|
104 | 88 |
(section, _) = TL.breakOn "«end»" (TL.drop 1 skipLine)
|