~ubuntu-branches/ubuntu/precise/ghc/precise

« back to all changes in this revision

Viewing changes to libraries/Cabal/tests/UnitTest/Distribution/ParseUtils.hs

  • Committer: Bazaar Package Importer
  • Author(s): Joachim Breitner
  • Date: 2011-01-17 12:49:24 UTC
  • Revision ID: james.westby@ubuntu.com-20110117124924-do1pym1jlf5o636m
Tags: upstream-7.0.1
ImportĀ upstreamĀ versionĀ 7.0.1

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
-----------------------------------------------------------------------------
 
2
-- |
 
3
-- Module      :  Distribution.ParseUtils
 
4
-- Copyright   :  (c) The University of Glasgow 2004
 
5
-- 
 
6
-- Maintainer  :  libraries@haskell.org
 
7
-- Stability   :  alpha
 
8
-- Portability :  portable
 
9
--
 
10
-- Utilities for parsing PackageDescription and InstalledPackageInfo.
 
11
 
 
12
 
 
13
{- All rights reserved.
 
14
 
 
15
Redistribution and use in source and binary forms, with or without
 
16
modification, are permitted provided that the following conditions are
 
17
met:
 
18
 
 
19
    * Redistributions of source code must retain the above copyright
 
20
      notice, this list of conditions and the following disclaimer.
 
21
 
 
22
    * Redistributions in binary form must reproduce the above
 
23
      copyright notice, this list of conditions and the following
 
24
      disclaimer in the documentation and/or other materials provided
 
25
      with the distribution.
 
26
 
 
27
    * Neither the name of the University nor the names of other
 
28
      contributors may be used to endorse or promote products derived
 
29
      from this software without specific prior written permission.
 
30
 
 
31
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
 
32
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
 
33
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
 
34
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
 
35
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
 
36
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
 
37
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
 
38
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
 
39
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
 
40
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
 
41
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}
 
42
 
 
43
module UnitTest.Distribution.ParseUtils where
 
44
 
 
45
import Distribution.ParseUtils
 
46
import Distribution.Compiler (CompilerFlavor, parseCompilerFlavorCompat)
 
47
import Distribution.License (License)
 
48
import Distribution.Version
 
49
import Distribution.Package     ( parsePackageName )
 
50
import Distribution.Compat.ReadP as ReadP hiding (get)
 
51
import Distribution.Simple.Utils (intercalate)
 
52
import Language.Haskell.Extension (Extension)
 
53
 
 
54
import Text.PrettyPrint.HughesPJ hiding (braces)
 
55
import Data.Char (isSpace, isUpper, toLower, isAlphaNum, isSymbol, isDigit)
 
56
import Data.Maybe       (fromMaybe)
 
57
import Data.Tree as Tree (Tree(..), flatten)
 
58
 
 
59
import Test.HUnit (Test(..), assertBool, Assertion, runTestTT, Counts, assertEqual)
 
60
import IO
 
61
import System.Environment ( getArgs )
 
62
import Control.Monad ( zipWithM_ )
 
63
 
 
64
------------------------------------------------------------------------------
 
65
-- TESTING
 
66
 
 
67
test_readFields = case 
 
68
                    readFields testFile 
 
69
                  of
 
70
                    ParseOk _ x -> x == expectedResult
 
71
                    _ -> False
 
72
  where 
 
73
    testFile = unlines $
 
74
          [ "Cabal-version: 3"
 
75
          , ""
 
76
          , "Description: This is a test file   "
 
77
          , "  with a description longer than two lines.  "
 
78
          , "if os(windows) {"
 
79
          , "  License:  You may not use this software"
 
80
          , "    ."
 
81
          , "    If you do use this software you will be seeked and destroyed."
 
82
          , "}"
 
83
          , "if os(linux) {"
 
84
          , "  Main-is:  foo1  "
 
85
          , "}"
 
86
          , ""
 
87
          , "if os(vista) {"
 
88
          , "  executable RootKit {"
 
89
          , "    Main-is: DRMManager.hs"
 
90
          , "  }"
 
91
          , "} else {"
 
92
          , "  executable VistaRemoteAccess {"
 
93
          , "    Main-is: VCtrl"
 
94
          , "}}"
 
95
          , ""
 
96
          , "executable Foo-bar {"
 
97
          , "  Main-is: Foo.hs"
 
98
          , "}"
 
99
          ]
 
100
    expectedResult = 
 
101
          [ F 1 "cabal-version" "3"
 
102
          , F 3 "description" 
 
103
                  "This is a test file\nwith a description longer than two lines."
 
104
          , IfBlock 5 "os(windows) " 
 
105
              [ F 6 "license" 
 
106
                      "You may not use this software\n\nIf you do use this software you will be seeked and destroyed."
 
107
              ]
 
108
              []
 
109
          , IfBlock 10 "os(linux) " 
 
110
              [ F 11 "main-is" "foo1" ] 
 
111
              [ ]
 
112
          , IfBlock 14 "os(vista) " 
 
113
              [ Section 15 "executable" "RootKit " 
 
114
                [ F 16 "main-is" "DRMManager.hs"]
 
115
              ] 
 
116
              [ Section 19 "executable" "VistaRemoteAccess "
 
117
                 [F 20 "main-is" "VCtrl"]
 
118
              ]
 
119
          , Section 23 "executable" "Foo-bar " 
 
120
              [F 24 "main-is" "Foo.hs"]
 
121
          ]
 
122
 
 
123
test_readFieldsCompat' = case test_readFieldsCompat of
 
124
                           ParseOk _ fs -> mapM_ (putStrLn . show) fs
 
125
                           x -> putStrLn $ "Failed: " ++ show x
 
126
test_readFieldsCompat = readFields testPkgDesc
 
127
  where 
 
128
    testPkgDesc = unlines [
 
129
        "-- Required",
 
130
        "Name: Cabal",
 
131
        "Version: 0.1.1.1.1-rain",
 
132
        "License: LGPL",
 
133
        "License-File: foo",
 
134
        "Copyright: Free Text String",
 
135
        "Cabal-version: >1.1.1",
 
136
        "-- Optional - may be in source?",
 
137
        "Author: Happy Haskell Hacker",
 
138
        "Homepage: http://www.haskell.org/foo",
 
139
        "Package-url: http://www.haskell.org/foo",
 
140
        "Synopsis: a nice package!",
 
141
        "Description: a really nice package!",
 
142
        "Category: tools",
 
143
        "buildable: True",
 
144
        "CC-OPTIONS: -g -o",
 
145
        "LD-OPTIONS: -BStatic -dn",
 
146
        "Frameworks: foo",
 
147
        "Tested-with: GHC",
 
148
        "Stability: Free Text String",
 
149
        "Build-Depends: haskell-src, HUnit>=1.0.0-rain",
 
150
        "Other-Modules: Distribution.Package, Distribution.Version,",
 
151
        "                Distribution.Simple.GHCPackageConfig",
 
152
        "Other-files: file1, file2",
 
153
        "Extra-Tmp-Files:    file1, file2",
 
154
        "C-Sources: not/even/rain.c, such/small/hands",
 
155
        "HS-Source-Dirs: src, src2",
 
156
        "Exposed-Modules: Distribution.Void, Foo.Bar",
 
157
        "Extensions: OverlappingInstances, TypeSynonymInstances",
 
158
        "Extra-Libraries: libfoo, bar, bang",
 
159
        "Extra-Lib-Dirs: \"/usr/local/libs\"",
 
160
        "Include-Dirs: your/slightest, look/will",
 
161
        "Includes: /easily/unclose, /me, \"funky, path\\\\name\"",
 
162
        "Install-Includes: /easily/unclose, /me, \"funky, path\\\\name\"",
 
163
        "GHC-Options: -fTH -fglasgow-exts",
 
164
        "Hugs-Options: +TH",
 
165
        "Nhc-Options: ",
 
166
        "Jhc-Options: ",
 
167
        "",
 
168
        "-- Next is an executable",
 
169
        "Executable: somescript",
 
170
        "Main-is: SomeFile.hs",
 
171
        "Other-Modules: Foo1, Util, Main",
 
172
        "HS-Source-Dir: scripts",
 
173
        "Extensions: OverlappingInstances",
 
174
        "GHC-Options: ",
 
175
        "Hugs-Options: ",
 
176
        "Nhc-Options: ",
 
177
        "Jhc-Options: "
 
178
        ]
 
179
{-
 
180
test' = do h <- openFile "../Cabal.cabal" ReadMode
 
181
           s <- hGetContents h
 
182
           let r = readFields s
 
183
           case r of
 
184
             ParseOk _ fs -> mapM_ (putStrLn . show) fs
 
185
             x -> putStrLn $ "Failed: " ++ show x
 
186
           putStrLn "==================="
 
187
           mapM_ (putStrLn . show) $
 
188
                 merge . zip [1..] . lines $ s
 
189
           hClose h
 
190
-}
 
191
 
 
192
-- ghc -DDEBUG --make Distribution/ParseUtils.hs -o test
 
193
 
 
194
main :: IO ()
 
195
main = do
 
196
  inputFiles <- getArgs
 
197
  ok <- mapM checkResult inputFiles
 
198
 
 
199
  zipWithM_ summary inputFiles ok
 
200
  putStrLn $ show (length (filter not ok)) ++ " out of " ++ show (length ok) ++ " failed"
 
201
 
 
202
  where summary f True  = return ()
 
203
        summary f False = putStrLn $ f  ++ " failed :-("
 
204
 
 
205
checkResult :: FilePath -> IO Bool
 
206
checkResult inputFile = do
 
207
  file <- readTextFile inputFile
 
208
  case readFields file of
 
209
    ParseOk _ result -> do
 
210
       hPutStrLn stderr $ inputFile ++ " parses ok :-)"
 
211
       return True
 
212
    ParseFailed err -> do
 
213
       hPutStrLn stderr $ inputFile ++ " parse failed:"
 
214
       hPutStrLn stderr $ show err
 
215
       return False