| 
					
				 | 
			
			
				@@ -1,18 +1,18 @@ 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 {-# LANGUAGE OverloadedStrings #-} 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				  
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-module Collage.Commands.Splice (runSplice, findFragments) where 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+module Collage.Commands.Splice(runSplice) where 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				  
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 import           Control.Monad (foldM) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 import qualified Data.Map as M 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 import qualified Data.Text as T 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 import qualified Data.Text.Lazy as TL 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 import qualified Data.Text.Lazy.IO as TL 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-import qualified System.Exit as Sys 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 import           System.FilePath ((</>)) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 import qualified System.FilePath as Sys 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				  
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 import Collage.Config 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 import Collage.Opts 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+import Collage.Utils 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				  
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 findFragmentIdentifiers :: TL.Text -> [T.Text] 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 findFragmentIdentifiers t 
			 | 
		
	
	
		
			
				| 
					
				 | 
			
			
				@@ -21,64 +21,51 @@ findFragmentIdentifiers t 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				   , not (TL.null f) = TL.toStrict f : findFragmentIdentifiers rs' 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				   | otherwise = [] 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				  
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+newtype Fragment = Fragment [T.Text] deriving (Eq, Show) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+ 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 toIdent :: T.Text -> TL.Text 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 toIdent = TL.fromStrict . T.cons '«' . flip T.snoc '»' 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				  
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-findFragments :: FilePath -> T.Text -> [Source] -> Either String (IO TL.Text) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+findFragments :: FilePath -> T.Text -> [Source] -> Either TL.Text (IO TL.Text) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 findFragments root s sources = case (T.splitOn "/" s) of 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-    [] -> error "(should not happen)" 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+    [] -> throw "Invalid empty fragment name!" 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				     (x:rs) -> case [ src 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				                    | src@Source { sourceName = n } <- sources 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				                    , n == x 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				                    ] of 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				                [src] -> go src rs (sourceExpose src) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-               []  -> Left ("Unable to find source named " ++ T.unpack x) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-               _   -> Left ("Ambiguous source name: " ++ T.unpack x) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+               []  -> throw ("Unable to find source named " % stext) x 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+               _   -> throw ("Ambiguous source name: " % stext) x 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				   where 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-    go :: Source -> [T.Text] -> Expose -> Either String (IO TL.Text) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+ 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				     go q [] (ExposeFile path) = 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				       return (TL.readFile (root </> sourceDir q </> path)) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				     go _ [] ExposeSections{} = 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-      Left $ concat [ "Splice identifier «" 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , T.unpack s 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , "» matches a file with sections, but " 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , "does not specify a section!" 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    ] 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+      throw ("Splice identifier «" % stext % 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+             "» matches a file with sections") s 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				     go _ [] NamedMap{} = 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-      Left $ concat [ "Splice identifier «" 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , T.unpack s 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , "» matches a map, but does not specify " 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , "a key!" 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    ] 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+      throw ("Splice identifier «" % stext % 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+             "» matches a map, but does not specify a key!") s 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				  
			 | 
		
	
		
			
				 | 
				 | 
			
			
				     go q [section] (ExposeSections path) = 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				       return (readSection (root </> sourceDir q </> path) section) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				  
			 | 
		
	
		
			
				 | 
				 | 
			
			
				     go _ (_:_) (ExposeSections path) = 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-      Left $ concat [ "Splice identifier «" 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , T.unpack s 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , "» indexes too far into the path " 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , path 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , "!" 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    ] 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+      throw ("Splice identifier «" % stext % 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+             "» indexes too far into the path " % string % "!") 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+        s path 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				  
			 | 
		
	
		
			
				 | 
				 | 
			
			
				     go _ (_:_) (ExposeFile path) = 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-      Left $ concat [ "Splice identifier «" 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , T.unpack s 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , "» indexes too far into the file " 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , path 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , "!" 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    ] 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+      throw ("Splice identifier «" % stext % 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+             "» indexes too far into the file " % string % "!") 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+        s path 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				  
			 | 
		
	
		
			
				 | 
				 | 
			
			
				     go q (k:rs) (NamedMap m) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				       | Just e <- M.lookup k m = go q rs e 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-      | otherwise = Left $ concat 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    [ "Splice identifier «" 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , T.unpack s 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , "» references a key " 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , T.unpack k 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    , " which cannot be found." 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                    ] 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+      | otherwise = throw 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+          ("Splice identifier «" % stext % 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+           "» references a key " % stext % 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+           " which cannot be found.") s k 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				  
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 doReplacements :: FilePath -> [Source] -> TL.Text -> IO TL.Text 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 doReplacements root e original = 
			 | 
		
	
	
		
			
				| 
					
				 | 
			
			
				@@ -86,7 +73,7 @@ doReplacements root e original = 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				   where 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				     doReplace file frag = do 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				       new <- case findFragments root frag e of 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-        Left err -> Sys.die err 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+        Left err -> cError err 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				         Right x  -> x 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				       return (TL.replace (toIdent frag) new file) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				  
			 | 
		
	
	
		
			
				| 
					
				 | 
			
			
				@@ -94,11 +81,8 @@ readSection :: FilePath -> T.Text -> IO TL.Text 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				 readSection path f = do 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				   contents <- TL.readFile path 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				   case TL.breakOn (toIdent f) contents of 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-    (_, "") -> Sys.die $ unwords [ "Unable to find section" 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                                 , show f 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                                 , "in file" 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                                 , path 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				-                                 ] 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+    (_, "") -> cError (format ("Unable to find section " % shown % 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				+                               " in file " % string) f path) 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				     (_, rs) -> 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				       let (_, skipLine) = TL.breakOn "\n" rs 
			 | 
		
	
		
			
				 | 
				 | 
			
			
				           (section, _) = TL.breakOn "«end»" (TL.drop 1 skipLine) 
			 |