~ubuntu-branches/ubuntu/utopic/bnfc/utopic

« back to all changes in this revision

Viewing changes to formats/ocaml/OCamlUtil.hs

  • Committer: Package Import Robot
  • Author(s): Joachim Breitner
  • Date: 2013-05-24 12:49:41 UTC
  • mfrom: (7.1.1 experimental)
  • Revision ID: package-import@ubuntu.com-20130524124941-tepbsbvdogyegb6k
Tags: 2.6.0.3-2
* Change Homepage field (Closes: #677988)
* Enable compat level 9
* Bump standards version to 3.9.4

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
{-
2
 
    BNF Converter: OCaml backend utility module
3
 
    Copyright (C) 2005  Author:  Kristofer Johannisson
4
 
 
5
 
    This program is free software; you can redistribute it and/or modify
6
 
    it under the terms of the GNU General Public License as published by
7
 
    the Free Software Foundation; either version 2 of the License, or
8
 
    (at your option) any later version.
9
 
 
10
 
    This program is distributed in the hope that it will be useful,
11
 
    but WITHOUT ANY WARRANTY; without even the implied warranty of
12
 
    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
13
 
    GNU General Public License for more details.
14
 
 
15
 
    You should have received a copy of the GNU General Public License
16
 
    along with this program; if not, write to the Free Software
17
 
    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
18
 
-}
19
 
 
20
 
module OCamlUtil where
21
 
 
22
 
import CF
23
 
import Utils
24
 
import Data.Char (toLower, toUpper)
25
 
 
26
 
fixType :: Cat -> String
27
 
fixType s = case s of
28
 
    '[':xs -> case break (== ']') xs of 
29
 
        (t,"]") -> fixType t +++ "list"
30
 
        _ -> s -- should not occur (this means an invariant of the type Cat is broken)
31
 
    "Integer" -> "int"
32
 
    "Double" -> "float"
33
 
    c:cs -> toLower c : cs
34
 
    _ -> s
35
 
    
36
 
fixTypeUpper :: Cat -> String
37
 
fixTypeUpper c = case fixType c of
38
 
    [] -> []
39
 
    c:cs -> toUpper c : cs
40
 
    
41
 
    
42
 
reservedOCaml :: [String]
43
 
reservedOCaml = [
44
 
    "and","as","assert","asr","begin","class",
45
 
    "constraint","do","done","downto","else","end", 
46
 
    "exception","external","false","for","fun","function", 
47
 
    "functor","if","in","include","inherit","initializer", 
48
 
    "land","lazy","let","lor","lsl","lsr", 
49
 
    "lxor","match","method","mod","module","mutable", 
50
 
    "new","object","of","open","or","private",
51
 
    "rec","sig","struct","then","to","true", 
52
 
    "try","type","val","virtual","when","while","with"]
53
 
    
54
 
mkTuple :: [String] -> String
55
 
mkTuple [] = ""
56
 
mkTuple [x] = x
57
 
mkTuple (x:xs) = "(" ++ foldl (\acc e -> acc ++ "," +++ e) x xs ++ ")"
58
 
 
59
 
insertBar :: [String] -> [String]
60
 
insertBar [] = []
61
 
insertBar [x]    = ["    " ++ x]
62
 
insertBar (x:xs) = ("    " ++ x ) :  map ("  | " ++) xs
63
 
 
64
 
mutualDefs :: [String] -> [String]
65
 
mutualDefs defs = case defs of
66
 
     []   -> []
67
 
     [d]  -> ["let rec" +++ d]
68
 
     d:ds -> ("let rec" +++ d) : map ("and" +++) ds