Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / PyValue.hs @ c92b4671

History | View | Annotate | Download (2.9 kB)

1 b711450c Petr Pudlak
{-| PyValue 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 2886c58d Petr Pudlak
{-# LANGUAGE ExistentialQuantification #-}
31 6c1a9fae Petr Pudlak
module Ganeti.PyValue
32 6c1a9fae Petr Pudlak
  ( PyValue(..)
33 6c1a9fae Petr Pudlak
  , PyValueEx(..)
34 6c1a9fae Petr Pudlak
  ) where
35 c4d68e39 Jose A. Lopes
36 c4d68e39 Jose A. Lopes
import Data.List (intercalate)
37 c4d68e39 Jose A. Lopes
import Data.Map (Map)
38 c4d68e39 Jose A. Lopes
import qualified Data.Map as Map
39 4651c69f Jose A. Lopes
import qualified Data.Set as Set (toList)
40 c4d68e39 Jose A. Lopes
41 4651c69f Jose A. Lopes
import Ganeti.BasicTypes
42 2886c58d Petr Pudlak
43 2886c58d Petr Pudlak
-- * PyValue represents data types convertible to Python
44 2886c58d Petr Pudlak
45 2886c58d Petr Pudlak
-- | Converts Haskell values into Python values
46 2886c58d Petr Pudlak
--
47 2886c58d Petr Pudlak
-- This is necessary for the default values of opcode parameters and
48 2886c58d Petr Pudlak
-- return values.  For example, if a default value or return type is a
49 2886c58d Petr Pudlak
-- Data.Map, then it must be shown as a Python dictioanry.
50 2886c58d Petr Pudlak
class PyValue a where
51 2886c58d Petr Pudlak
  showValue :: a -> String
52 c4d68e39 Jose A. Lopes
53 6c1a9fae Petr Pudlak
  showValueList :: [a] -> String
54 6c1a9fae Petr Pudlak
  showValueList xs =  "[" ++ intercalate "," (map showValue xs) ++ "]"
55 6c1a9fae Petr Pudlak
56 85bcb1de Jose A. Lopes
instance PyValue Bool where
57 85bcb1de Jose A. Lopes
  showValue = show
58 85bcb1de Jose A. Lopes
59 85bcb1de Jose A. Lopes
instance PyValue Int where
60 85bcb1de Jose A. Lopes
  showValue = show
61 85bcb1de Jose A. Lopes
62 85bcb1de Jose A. Lopes
instance PyValue Integer where
63 85bcb1de Jose A. Lopes
  showValue = show
64 85bcb1de Jose A. Lopes
65 85bcb1de Jose A. Lopes
instance PyValue Double where
66 85bcb1de Jose A. Lopes
  showValue = show
67 85bcb1de Jose A. Lopes
68 85bcb1de Jose A. Lopes
instance PyValue Char where
69 85bcb1de Jose A. Lopes
  showValue = show
70 6c1a9fae Petr Pudlak
  showValueList = show
71 c4d68e39 Jose A. Lopes
72 c4d68e39 Jose A. Lopes
instance (PyValue a, PyValue b) => PyValue (a, b) where
73 92b28956 Jose A. Lopes
  showValue (x, y) = "(" ++ showValue x ++ "," ++ showValue y ++ ")"
74 c4d68e39 Jose A. Lopes
75 14874844 Jose A. Lopes
instance (PyValue a, PyValue b, PyValue c) => PyValue (a, b, c) where
76 14874844 Jose A. Lopes
  showValue (x, y, z) =
77 14874844 Jose A. Lopes
    "(" ++
78 14874844 Jose A. Lopes
    showValue x ++ "," ++
79 14874844 Jose A. Lopes
    showValue y ++ "," ++
80 14874844 Jose A. Lopes
    showValue z ++
81 14874844 Jose A. Lopes
    ")"
82 14874844 Jose A. Lopes
83 c4d68e39 Jose A. Lopes
instance PyValue a => PyValue [a] where
84 6c1a9fae Petr Pudlak
  showValue = showValueList
85 c4d68e39 Jose A. Lopes
86 c4d68e39 Jose A. Lopes
instance (PyValue k, PyValue a) => PyValue (Map k a) where
87 c4d68e39 Jose A. Lopes
  showValue mp =
88 c4d68e39 Jose A. Lopes
    "{" ++ intercalate ", " (map showPair (Map.assocs mp)) ++ "}"
89 92b28956 Jose A. Lopes
    where showPair (k, x) = showValue k ++ ":" ++ showValue x
90 c4d68e39 Jose A. Lopes
91 4651c69f Jose A. Lopes
instance PyValue a => PyValue (ListSet a) where
92 4651c69f Jose A. Lopes
  showValue = showValue . Set.toList . unListSet
93 2886c58d Petr Pudlak
94 2886c58d Petr Pudlak
-- * PyValue represents an unspecified value convertible to Python
95 2886c58d Petr Pudlak
96 2886c58d Petr Pudlak
-- | Encapsulates Python default values
97 2886c58d Petr Pudlak
data PyValueEx = forall a. PyValue a => PyValueEx a
98 2886c58d Petr Pudlak
99 2886c58d Petr Pudlak
instance PyValue PyValueEx where
100 2886c58d Petr Pudlak
  showValue (PyValueEx x) = showValue x