module Propellor.Property.ConfFile (
	
	SectionStart,
	SectionPast,
	AdjustSection,
	InsertSection,
	adjustSection,
	
	IniSection,
	IniKey,
	containsIniSetting,
	lacksIniSection,
) where
import Propellor
import Propellor.Property.File
import Data.List (isPrefixOf, foldl')
type SectionStart  = Line -> Bool
type SectionPast   = Line -> Bool
type AdjustSection = [Line] -> [Line] 
type InsertSection = [Line] -> [Line]
adjustSection
	:: Desc
	-> SectionStart
	-> SectionPast
	-> AdjustSection
	-> InsertSection
	-> FilePath
	-> Property NoInfo
adjustSection desc start past adjust insert = fileProperty desc go
  where
	go ls = let (pre, wanted, post) = foldl' find ([], [], []) ls
		in if null wanted
			then insert ls
			else pre ++ (adjust wanted) ++ post
	find (pre, wanted, post) l
		| null wanted && null post && (not . start) l =
			(pre ++ [l], wanted, post)
		| (start l && null wanted && null post)
		  || ((not . null) wanted && null post && (not . past) l) =
			  (pre, wanted ++ [l], post)
		| otherwise = (pre, wanted, post ++ [l])
type IniSection = String
type IniKey = String
iniHeader :: IniSection -> String
iniHeader header = '[' : header ++ "]"
adjustIniSection
	:: Desc
	-> IniSection
	-> AdjustSection
	-> InsertSection
	-> FilePath
	-> Property NoInfo
adjustIniSection desc header =
	adjustSection
	desc
	(== iniHeader header)
	("[" `isPrefixOf`)
containsIniSetting :: FilePath -> (IniSection, IniKey, String) -> Property NoInfo
containsIniSetting f (header, key, value) =
	adjustIniSection
	(f ++ " section [" ++ header ++ "] contains " ++ key ++ "=" ++ value)
	header
	go
	(++ [confheader, confline]) 
	f
  where
	confheader = iniHeader header
	confline   = key ++ "=" ++ value
	go []      = [confline]
	go (l:ls)  = if isKeyVal l then confline : ls else l : (go ls)
	isKeyVal x = (filter (/= ' ') . takeWhile (/= '=')) x `elem` [key, '#':key]
lacksIniSection :: FilePath -> IniSection -> Property NoInfo
lacksIniSection f header =
	adjustIniSection
	(f ++ " lacks section [" ++ header ++ "]")
	header
	(const []) 
	id 
	f