Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / PyValue.hs @ b9202225

History | View | Annotate | Download (2.9 kB)

1
{-| PyValue 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 ExistentialQuantification #-}
31
module Ganeti.PyValue
32
  ( PyValue(..)
33
  , PyValueEx(..)
34
  ) where
35

    
36
import Data.List (intercalate)
37
import Data.Map (Map)
38
import qualified Data.Map as Map
39
import qualified Data.Set as Set (toList)
40

    
41
import Ganeti.BasicTypes
42

    
43
-- * PyValue represents data types convertible to Python
44

    
45
-- | Converts Haskell values into Python values
46
--
47
-- This is necessary for the default values of opcode parameters and
48
-- return values.  For example, if a default value or return type is a
49
-- Data.Map, then it must be shown as a Python dictioanry.
50
class PyValue a where
51
  showValue :: a -> String
52

    
53
  showValueList :: [a] -> String
54
  showValueList xs =  "[" ++ intercalate "," (map showValue xs) ++ "]"
55

    
56
instance PyValue Bool where
57
  showValue = show
58

    
59
instance PyValue Int where
60
  showValue = show
61

    
62
instance PyValue Integer where
63
  showValue = show
64

    
65
instance PyValue Double where
66
  showValue = show
67

    
68
instance PyValue Char where
69
  showValue = show
70
  showValueList = show
71

    
72
instance (PyValue a, PyValue b) => PyValue (a, b) where
73
  showValue (x, y) = "(" ++ showValue x ++ "," ++ showValue y ++ ")"
74

    
75
instance (PyValue a, PyValue b, PyValue c) => PyValue (a, b, c) where
76
  showValue (x, y, z) =
77
    "(" ++
78
    showValue x ++ "," ++
79
    showValue y ++ "," ++
80
    showValue z ++
81
    ")"
82

    
83
instance PyValue a => PyValue [a] where
84
  showValue = showValueList
85

    
86
instance (PyValue k, PyValue a) => PyValue (Map k a) where
87
  showValue mp =
88
    "{" ++ intercalate ", " (map showPair (Map.assocs mp)) ++ "}"
89
    where showPair (k, x) = showValue k ++ ":" ++ showValue x
90

    
91
instance PyValue a => PyValue (ListSet a) where
92
  showValue = showValue . Set.toList . unListSet
93

    
94
-- * PyValue represents an unspecified value convertible to Python
95

    
96
-- | Encapsulates Python default values
97
data PyValueEx = forall a. PyValue a => PyValueEx a
98

    
99
instance PyValue PyValueEx where
100
  showValue (PyValueEx x) = showValue x