| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Servant.Reason
Description
Basic usage:
import MyLib (MyServantApiType)
import Servant.Reason
spec :: Spec
spec = Spec ["Generated", "MyApi"]
(defReasonImports : generateReasonForAPI (Proxy :: Proxy MyServantApiType))
main :: IO ()
main = specsToDir [spec] "my-reason-dir"Synopsis
- generateReasonForAPI :: (HasForeign LangReason ReasonDatatype api, GenerateList ReasonDatatype (Foreign ReasonDatatype api)) => Proxy api -> [Text]
- generateReasonForAPIWith :: (HasForeign LangReason ReasonDatatype api, GenerateList ReasonDatatype (Foreign ReasonDatatype api)) => ReasonOptions -> Proxy api -> [Text]
- data ReasonOptions = ReasonOptions {}
- data UrlPrefix
- defReasonOptions :: ReasonOptions
- defReasonImports :: Text
- data Spec = Spec [Text] [Text]
- class ReasonType a
- specsToDir :: [Spec] -> FilePath -> IO ()
- data Proxy (t :: k) :: forall k. k -> Type = Proxy
Documentation
generateReasonForAPI :: (HasForeign LangReason ReasonDatatype api, GenerateList ReasonDatatype (Foreign ReasonDatatype api)) => Proxy api -> [Text] Source #
Generate Reason code for the API with default options.
Returns a list of Reason functions to query your Servant API from Reason.
You could spit these out to a file and call them from your Reason code, but you
would be better off creating a Spec with the result and using specsToDir,
which handles the module name for you.
generateReasonForAPIWith :: (HasForeign LangReason ReasonDatatype api, GenerateList ReasonDatatype (Foreign ReasonDatatype api)) => ReasonOptions -> Proxy api -> [Text] Source #
Generate Reason code for the API with custom options.
data ReasonOptions Source #
Options to configure how code is generated.
Constructors
| ReasonOptions | |
Fields
| |
defReasonOptions :: ReasonOptions Source #
Default options for generating Reason code.
The default options are:
{ urlPrefix =
Static ""
, reasonExportOptions =
Reason.defaultOptions
, emptyResponseReasonTypes =
[ toReasonType NoContent ]
, stringReasonTypes =
[ toReasonType "" ]
}defReasonImports :: Text Source #
Default imports required by generated Reason code.
You probably want to include this at the top of your generated Reason module.
Convenience re-exports from the Reason module
class ReasonType a #
Instances
specsToDir :: [Spec] -> FilePath -> IO () #
Convenience re-exports from Data.Proxy
data Proxy (t :: k) :: forall k. k -> Type #
Proxy is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically, is a safer alternative to the
Proxy :: Proxy a'undefined :: a' idiom.
>>>Proxy :: Proxy (Void, Int -> Int)Proxy
Proxy can even hold types of higher kinds,
>>>Proxy :: Proxy EitherProxy
>>>Proxy :: Proxy FunctorProxy
>>>Proxy :: Proxy complicatedStructureProxy
Constructors
| Proxy |
Instances
| Generic1 (Proxy :: k -> Type) | |
| Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| Foldable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
| Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| Contravariant (Proxy :: Type -> Type) | |
| Representable (Proxy :: Type -> Type) | |
| Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
| MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
| Bounded (Proxy t) | Since: base-4.7.0.0 |
| Enum (Proxy s) | Since: base-4.7.0.0 |
| Eq (Proxy s) | Since: base-4.7.0.0 |
| Ord (Proxy s) | Since: base-4.7.0.0 |
| Read (Proxy t) | Since: base-4.7.0.0 |
| Show (Proxy s) | Since: base-4.7.0.0 |
| Ix (Proxy s) | Since: base-4.7.0.0 |
Defined in Data.Proxy | |
| Generic (Proxy t) | |
| Semigroup (Proxy s) | Since: base-4.9.0.0 |
| Monoid (Proxy s) | Since: base-4.7.0.0 |
| ReasonType a => ReasonType (Proxy a) | |
Defined in Reason.Type Methods toReasonType :: Proxy a -> ReasonDatatype # | |
| type Rep1 (Proxy :: k -> Type) | Since: base-4.6.0.0 |
| type Rep (Proxy :: Type -> Type) | |
| type Rep (Proxy t) | Since: base-4.6.0.0 |