Hs2Py constants: add 'osApiVersions'
[ganeti-local] / src / Ganeti / PyValueInstances.hs
1 {-| PyValueInstances contains instances for the 'PyValue' typeclass.
2
3 The typeclass 'PyValue' converts Haskell values to Python values.
4 This module contains instances of this typeclass for several generic
5 types.  These instances are used in the Haskell to Python generation
6 of opcodes and constants, for example.
7
8 -}
9
10 {-
11
12 Copyright (C) 2013 Google Inc.
13
14 This program is free software; you can redistribute it and/or modify
15 it under the terms of the GNU General Public License as published by
16 the Free Software Foundation; either version 2 of the License, or
17 (at your option) any later version.
18
19 This program is distributed in the hope that it will be useful, but
20 WITHOUT ANY WARRANTY; without even the implied warranty of
21 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
22 General Public License for more details.
23
24 You should have received a copy of the GNU General Public License
25 along with this program; if not, write to the Free Software
26 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
27 02110-1301, USA.
28
29 -}
30 {-# LANGUAGE FlexibleInstances, OverlappingInstances,
31              TypeSynonymInstances, IncoherentInstances #-}
32 {-# OPTIONS_GHC -fno-warn-orphans #-}
33 module Ganeti.PyValueInstances where
34
35 import Data.List (intercalate)
36 import Data.Map (Map)
37 import qualified Data.Map as Map
38 import qualified Data.Set as Set (toList)
39
40 import Ganeti.BasicTypes
41 import Ganeti.THH
42
43 instance PyValue Bool
44 instance PyValue Int
45 instance PyValue Double
46 instance PyValue Char
47
48 instance (PyValue a, PyValue b) => PyValue (a, b) where
49   showValue (x, y) = "(" ++ showValue x ++ "," ++ showValue y ++ ")"
50
51 instance (PyValue a, PyValue b, PyValue c) => PyValue (a, b, c) where
52   showValue (x, y, z) =
53     "(" ++
54     showValue x ++ "," ++
55     showValue y ++ "," ++
56     showValue z ++
57     ")"
58
59 instance PyValue String where
60   showValue = show
61
62 instance PyValue a => PyValue [a] where
63   showValue xs = "[" ++ intercalate "," (map showValue xs) ++ "]"
64
65 instance (PyValue k, PyValue a) => PyValue (Map k a) where
66   showValue mp =
67     "{" ++ intercalate ", " (map showPair (Map.assocs mp)) ++ "}"
68     where showPair (k, x) = showValue k ++ ":" ++ showValue x
69
70 instance PyValue a => PyValue (ListSet a) where
71   showValue = showValue . Set.toList . unListSet