Plan 9 from Bell Labs’s /usr/web/sources/contrib/fernan/nhc98/tests/nhc-bugs/ix-derived/Main.hs

Copyright © 2021 Plan 9 Foundation.
Distributed under the MIT License.
Download the Plan 9 distribution.


module Main where

import Array
import List
import Ix

data GMLOp
   = ConsOne
   | ConsTwo
    deriving (Show,Eq,Ord,Bounded,Enum,Ix)

{-
-- This is a dummy Ix (which leaverges Enum)
instance Ix GMLOp where
    range (a,b) = [a..b]
    index (ConsOne,ConsTwo) i = fromEnum i
    inRange (a,b) c = inRange (fromEnum a,fromEnum b) (fromEnum c)
-}

default (Int)

main = do
        print $ (minBound :: GMLOp)
        print $ (maxBound :: GMLOp)
        print $ (fromEnum (maxBound :: GMLOp))
        print $ range (minBound :: GMLOp,maxBound::GMLOp)
        print $ sort (range (minBound :: GMLOp,maxBound::GMLOp))
        print $ rangeSize (minBound :: GMLOp,maxBound::GMLOp)
        print $ inRange (minBound :: GMLOp,maxBound::GMLOp) ConsOne
        print $ inRange (minBound :: GMLOp,maxBound::GMLOp) ConsTwo

        print ((minBound :: GMLOp,maxBound::GMLOp) ,
              [ (i,()) | i <- [(minBound::GMLOp)..maxBound] ])


Bell Labs OSI certified Powered by Plan 9

(Return to Plan 9 Home Page)

Copyright © 2021 Plan 9 Foundation. All Rights Reserved.
Comments to webmaster@9p.io.