{-# LINE 1 "CLexType.hs" #-} {-# LINE 1 "CLexType.hsc" #-} {-# LINE 2 "CLexType.hs" #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LINE 2 "CLexType.hsc" #-} module Data.JsonStream.CLexType where import Foreign.C.Types import Foreign newtype LexResultType = LexResultType CInt deriving (Show, Eq, Storable) {-# LINE 10 "CLexType.hsc" #-} resNumber :: LexResultType resNumber = LexResultType 0 resString :: LexResultType resString = LexResultType 1 resTrue :: LexResultType resTrue = LexResultType 2 resFalse :: LexResultType resFalse = LexResultType 3 resNull :: LexResultType resNull = LexResultType 4 resOpenBrace :: LexResultType resOpenBrace = LexResultType 5 resCloseBrace :: LexResultType resCloseBrace = LexResultType 6 resOpenBracket :: LexResultType resOpenBracket = LexResultType 7 resCloseBracket :: LexResultType resCloseBracket = LexResultType 8 resStringPartial :: LexResultType resStringPartial = LexResultType 9 resStringUni :: LexResultType resStringUni = LexResultType 11 resNumberPartial :: LexResultType resNumberPartial = LexResultType 10 resNumberSmall :: LexResultType resNumberSmall = LexResultType 12 {-# LINE 28 "CLexType.hsc" #-}