Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / PyValueInstances.hs @ 96e3dfa7

History | View | Annotate | Download (2.4 kB)

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