Skip to content

Commit

Permalink
Make Parse.hsc a regular module Parse.hs
Browse files Browse the repository at this point in the history
Liquid Haskell can't collect specs in .hsc files.
See ucsd-progsys/liquidhaskell#2132
  • Loading branch information
facundominguez committed Oct 25, 2023
1 parent 13ef16c commit 5b4f900
Show file tree
Hide file tree
Showing 2 changed files with 28 additions and 28 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -3,49 +3,23 @@
--
-- Bindings for @<R/R_ext/Parse.h>@.

{-# LANGUAGE CPP #-}
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ForeignFunctionInterface #-}

#include <Rinternals.h>
#include <R_ext/Parse.h>
module Foreign.R.Parse
( parseVector
, ParseStatus(..)
) where

import Foreign.R.Type (ParseStatus(..))
import qualified Foreign.R as R

import Foreign
import Foreign.C

-- | The return code of a call to 'parseVector', indicating whether the parser
-- failed or succeeded.
data ParseStatus
= PARSE_NULL
| PARSE_OK
| PARSE_INCOMPLETE
| PARSE_ERROR
| PARSE_EOF
deriving (Eq, Show)

instance Enum ParseStatus where
fromEnum PARSE_NULL = #const PARSE_NULL
fromEnum PARSE_OK = #const PARSE_OK
fromEnum PARSE_INCOMPLETE = #const PARSE_INCOMPLETE
fromEnum PARSE_ERROR = #const PARSE_ERROR
fromEnum PARSE_EOF = #const PARSE_EOF
toEnum i = case i of
(#const PARSE_NULL) -> PARSE_NULL
(#const PARSE_OK) -> PARSE_OK
(#const PARSE_INCOMPLETE) -> PARSE_INCOMPLETE
(#const PARSE_ERROR) -> PARSE_ERROR
(#const PARSE_EOF) -> PARSE_EOF
_ -> error "ParseStatus.fromEnum: can't mach value"

-- | @parseVector text num status source@ parses the input string into an AST.
-- @source@, if provided, names the origin of @text@ (e.g. a filename). @num@
-- limits the number of expressions to parse, or @-1@ if no limit.
Expand All @@ -59,6 +33,6 @@ parseVector
-> IO (R.SEXP s)
parseVector (R.unsexp -> s) (fromIntegral -> cnt) reti (R.unsexp -> input) =
R.sexp <$> c_parseVector s cnt reti input

foreign import ccall "R_ext/Parse.h R_ParseVector" c_parseVector
:: R.SEXP0 -> CInt -> Ptr CInt -> R.SEXP0 -> IO R.SEXP0
26 changes: 26 additions & 0 deletions inline-r/src/Foreign/R/Type.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,7 @@ module Foreign.R.Type
, Sing
, Logical(..)
, PairList
, ParseStatus(..)
, IsVector
, IsGenericVector
, IsList
Expand All @@ -46,6 +47,7 @@ module Foreign.R.Type
) where

#include <Rinternals.h>
#include <R_ext/Parse.h>

import Foreign.R.Constraints
import Internal.Error
Expand Down Expand Up @@ -162,6 +164,30 @@ instance Enum SEXPTYPE where
instance NFData SEXPTYPE where
rnf = (`seq` ())

-- | The return code of a call to 'parseVector', indicating whether the parser
-- failed or succeeded.
data ParseStatus
= PARSE_NULL
| PARSE_OK
| PARSE_INCOMPLETE
| PARSE_ERROR
| PARSE_EOF
deriving (Eq, Show)

instance Enum ParseStatus where
fromEnum PARSE_NULL = #const PARSE_NULL
fromEnum PARSE_OK = #const PARSE_OK
fromEnum PARSE_INCOMPLETE = #const PARSE_INCOMPLETE
fromEnum PARSE_ERROR = #const PARSE_ERROR
fromEnum PARSE_EOF = #const PARSE_EOF
toEnum i = case i of
(#const PARSE_NULL) -> PARSE_NULL
(#const PARSE_OK) -> PARSE_OK
(#const PARSE_INCOMPLETE) -> PARSE_INCOMPLETE
(#const PARSE_ERROR) -> PARSE_ERROR
(#const PARSE_EOF) -> PARSE_EOF
_ -> error "ParseStatus.fromEnum: can't mach value"

genSingletons [''SEXPTYPE]

-- | Used where the R documentation speaks of "pairlists", which are really just
Expand Down

0 comments on commit 5b4f900

Please sign in to comment.