summaryrefslogtreecommitdiff
path: root/src/Propellor/Property/List.hs
blob: 0eec04c712fe5ff24a25bb7f4637810b026cc669 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Propellor.Property.List (
	props,
	Props,
	toProps,
	propertyList,
	combineProperties,
) where

import Propellor.Types
import Propellor.Types.Core
import Propellor.Types.MetaTypes
import Propellor.PropAccum
import Propellor.Engine
import Propellor.Exception

import Data.Monoid

toProps :: [Property (MetaTypes metatypes)] -> Props (MetaTypes metatypes)
toProps ps = Props (map toChildProperty ps)

-- | Combines a list of properties, resulting in a single property
-- that when run will run each property in the list in turn,
-- and print out the description of each as it's run. Does not stop
-- on failure; does propagate overall success/failure.
--
-- For example:
--
-- > propertyList "foo" $ props
-- > 	& bar
-- > 	& baz
propertyList :: SingI metatypes => Desc -> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList desc (Props ps) = 
	property desc (ensureChildProperties cs)
		`addChildren` cs
  where
	cs = map toChildProperty ps

-- | Combines a list of properties, resulting in one property that
-- ensures each in turn. Stops if a property fails.
combineProperties :: SingI metatypes => Desc -> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties desc (Props ps) = 
	property desc (combineSatisfy cs NoChange)
		`addChildren` cs
  where
	cs = map toChildProperty ps

combineSatisfy :: [ChildProperty] -> Result -> Propellor Result
combineSatisfy [] rs = return rs
combineSatisfy (p:ps) rs = do
	r <- catchPropellor $ getSatisfy p
	case r of
		FailedChange -> return FailedChange
		_ -> combineSatisfy ps (r <> rs)