Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / ConstantUtils.hs @ f2b6e7d4

History | View | Annotate | Download (1.8 kB)

1 f2b6e7d4 Jose A. Lopes
{-| ConstantUtils contains the helper functions for constants
2 f2b6e7d4 Jose A. Lopes
3 f2b6e7d4 Jose A. Lopes
This module cannot be merged with 'Ganeti.Utils' because it would
4 f2b6e7d4 Jose A. Lopes
create a circular dependency if imported, for example, from
5 f2b6e7d4 Jose A. Lopes
'Ganeti.Constants'.
6 f2b6e7d4 Jose A. Lopes
7 f2b6e7d4 Jose A. Lopes
-}
8 f2b6e7d4 Jose A. Lopes
9 f2b6e7d4 Jose A. Lopes
{-
10 f2b6e7d4 Jose A. Lopes
11 f2b6e7d4 Jose A. Lopes
Copyright (C) 2013 Google Inc.
12 f2b6e7d4 Jose A. Lopes
13 f2b6e7d4 Jose A. Lopes
This program is free software; you can redistribute it and/or modify
14 f2b6e7d4 Jose A. Lopes
it under the terms of the GNU General Public License as published by
15 f2b6e7d4 Jose A. Lopes
the Free Software Foundation; either version 2 of the License, or
16 f2b6e7d4 Jose A. Lopes
(at your option) any later version.
17 f2b6e7d4 Jose A. Lopes
18 f2b6e7d4 Jose A. Lopes
This program is distributed in the hope that it will be useful, but
19 f2b6e7d4 Jose A. Lopes
WITHOUT ANY WARRANTY; without even the implied warranty of
20 f2b6e7d4 Jose A. Lopes
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
21 f2b6e7d4 Jose A. Lopes
General Public License for more details.
22 f2b6e7d4 Jose A. Lopes
23 f2b6e7d4 Jose A. Lopes
You should have received a copy of the GNU General Public License
24 f2b6e7d4 Jose A. Lopes
along with this program; if not, write to the Free Software
25 f2b6e7d4 Jose A. Lopes
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
26 f2b6e7d4 Jose A. Lopes
02110-1301, USA.
27 f2b6e7d4 Jose A. Lopes
28 f2b6e7d4 Jose A. Lopes
-}
29 f2b6e7d4 Jose A. Lopes
module Ganeti.ConstantUtils where
30 f2b6e7d4 Jose A. Lopes
31 f2b6e7d4 Jose A. Lopes
import Data.Set (Set)
32 f2b6e7d4 Jose A. Lopes
import qualified Data.Set as Set (fromList, toList)
33 f2b6e7d4 Jose A. Lopes
34 f2b6e7d4 Jose A. Lopes
import Ganeti.THH (PyValue(..))
35 f2b6e7d4 Jose A. Lopes
import Ganeti.PyValueInstances ()
36 f2b6e7d4 Jose A. Lopes
37 f2b6e7d4 Jose A. Lopes
-- | FrozenSet wraps a Haskell 'Set'
38 f2b6e7d4 Jose A. Lopes
--
39 f2b6e7d4 Jose A. Lopes
-- See 'PyValue' instance for 'FrozenSet'.
40 f2b6e7d4 Jose A. Lopes
newtype FrozenSet a = FrozenSet { unFrozenSet :: Set a }
41 f2b6e7d4 Jose A. Lopes
  deriving (Show)
42 f2b6e7d4 Jose A. Lopes
43 f2b6e7d4 Jose A. Lopes
-- | Converts a Haskell 'Set' into a Python 'frozenset'
44 f2b6e7d4 Jose A. Lopes
--
45 f2b6e7d4 Jose A. Lopes
-- This instance was supposed to be for 'Set' instead of 'FrozenSet'.
46 f2b6e7d4 Jose A. Lopes
-- However, 'ghc-6.12.1' seems to be crashing with 'segmentation
47 f2b6e7d4 Jose A. Lopes
-- fault' due to the presence of more than one instance of 'Set',
48 f2b6e7d4 Jose A. Lopes
-- namely, this one and the one in 'Ganeti.OpCodes'.  For this reason,
49 f2b6e7d4 Jose A. Lopes
-- we wrap 'Set' into 'FrozenSet'.
50 f2b6e7d4 Jose A. Lopes
instance PyValue a => PyValue (FrozenSet a) where
51 f2b6e7d4 Jose A. Lopes
  showValue s = "frozenset(" ++ showValue (Set.toList (unFrozenSet s)) ++ ")"
52 f2b6e7d4 Jose A. Lopes
53 f2b6e7d4 Jose A. Lopes
mkSet :: Ord a => [a] -> FrozenSet a
54 f2b6e7d4 Jose A. Lopes
mkSet = FrozenSet . Set.fromList