Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / THH / Field.hs @ 72375ff8

History | View | Annotate | Download (3.1 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Helpers for creating various kinds of 'Field's.
4

    
5
They aren't directly needed for the Template Haskell code in Ganeti.THH,
6
so better keep them in a separate module.
7

    
8
-}
9

    
10
{-
11

    
12
Copyright (C) 2014 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

    
31
module Ganeti.THH.Field
32
  ( specialNumericalField
33
  , timeAsDoubleField
34
  , timeStampFields
35
  , uuidFields
36
  , serialFields
37
  , TagSet
38
  , tagsFields
39
  ) where
40

    
41
import Control.Monad
42
import qualified Data.Set as Set
43
import Language.Haskell.TH
44
import qualified Text.JSON as JSON
45
import System.Time (ClockTime(..))
46

    
47
import Ganeti.JSON
48
import Ganeti.THH
49

    
50
-- * Internal functions
51

    
52
-- | Wrapper around a special parse function, suitable as field-parsing
53
-- function.
54
numericalReadFn :: JSON.JSON a => (String -> JSON.Result a)
55
                   -> [(String, JSON.JSValue)] -> JSON.JSValue -> JSON.Result a
56
numericalReadFn _ _ v@(JSON.JSRational _ _) = JSON.readJSON v
57
numericalReadFn f _ (JSON.JSString x) = f $ JSON.fromJSString x
58
numericalReadFn _ _ _ = JSON.Error "A numerical field has to be a number or\
59
                                   \ a string."
60

    
61
-- | Sets the read function to also accept string parsable by the given
62
-- function.
63
specialNumericalField :: Name -> Field -> Field
64
specialNumericalField f field =
65
     field { fieldRead = Just (appE (varE 'numericalReadFn) (varE f)) }
66

    
67
-- | Creates a new mandatory field that reads time as the (floating point)
68
-- number of seconds since the standard UNIX epoch, and represents it in
69
-- Haskell as 'ClockTime'.
70
timeAsDoubleField :: String -> Field
71
timeAsDoubleField fname =
72
  (simpleField fname [t| ClockTime |])
73
    { fieldRead = Just $ [| \_ -> liftM unTimeAsDoubleJSON . JSON.readJSON |]
74
    , fieldShow = Just $ [| \c -> (JSON.showJSON $ TimeAsDoubleJSON c, []) |]
75
    }
76

    
77
-- * External functions and data types
78

    
79
-- | Timestamp fields description.
80
timeStampFields :: [Field]
81
timeStampFields = map (defaultField [| TOD 0 0 |] . timeAsDoubleField)
82
                      ["ctime", "mtime"]
83

    
84

    
85
-- | Serial number fields description.
86
serialFields :: [Field]
87
serialFields =
88
    [ renameField  "Serial" $ simpleField "serial_no" [t| Int |] ]
89

    
90
-- | UUID fields description.
91
uuidFields :: [Field]
92
uuidFields = [ simpleField "uuid" [t| String |] ]
93

    
94
-- | Tag set type alias.
95
type TagSet = Set.Set String
96

    
97
-- | Tag field description.
98
tagsFields :: [Field]
99
tagsFields = [ defaultField [| Set.empty |] $
100
               simpleField "tags" [t| TagSet |] ]