cachix-api-0.1.0.3: Servant HTTP API specification for https://cachix.org

Safe HaskellNone
LanguageHaskell2010

Cachix.Api.Types

Synopsis

Documentation

data NixCacheInfo Source #

Instances
Show NixCacheInfo Source # 
Instance details

Defined in Cachix.Api.Types

Generic NixCacheInfo Source # 
Instance details

Defined in Cachix.Api.Types

Associated Types

type Rep NixCacheInfo :: Type -> Type #

ToJSON NixCacheInfo Source # 
Instance details

Defined in Cachix.Api.Types

FromJSON NixCacheInfo Source # 
Instance details

Defined in Cachix.Api.Types

ToSchema NixCacheInfo Source # 
Instance details

Defined in Cachix.Api.Types

MimeUnrender XNixCacheInfo NixCacheInfo Source # 
Instance details

Defined in Cachix.Types.ContentTypes

type Rep NixCacheInfo Source # 
Instance details

Defined in Cachix.Api.Types

type Rep NixCacheInfo = D1 (MetaData "NixCacheInfo" "Cachix.Api.Types" "cachix-api-0.1.0.3-HMIesBjHyxfFikB1iuASsF" False) (C1 (MetaCons "NixCacheInfo" PrefixI True) (S1 (MetaSel (Just "storeDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "wantMassQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer) :*: S1 (MetaSel (Just "priority") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))))

data NarInfo Source #

Constructors

NarInfo 

Fields

  • storePath :: Text

    absolute path of the derivation in nix store

  • url :: Text

    relative url (to current domain) to download nar file

  • compression :: Text

    name of the compression algorithm, eg. xz

  • fileHash :: Text

    sha256 hash of the compressed nar file NOTE: to compute use "nix-hash --type sha256 --flat"

  • fileSize :: Integer

    file size of compressed nar file NOTE: du -b

  • narHash :: Text

    sha256 hash of the decompressed nar file NOTE: to compute use "nix-hash --type sha256 --flat --base32"

  • narSize :: Integer

    file size of decompressed nar file NOTE: du -b

  • references :: [Text]

    immediate dependencies of the storePath NOTE: nix-store -q --references

  • deriver :: Text

    relative store path (to nix store root) of the deriver NOTE: nix-store -q --deriver

  • sig :: Text

    signature of fields: storePath, narHash, narSize, refs

Instances
Show NarInfo Source # 
Instance details

Defined in Cachix.Api.Types

Generic NarInfo Source # 
Instance details

Defined in Cachix.Api.Types

Associated Types

type Rep NarInfo :: Type -> Type #

Methods

from :: NarInfo -> Rep NarInfo x #

to :: Rep NarInfo x -> NarInfo #

ToJSON NarInfo Source # 
Instance details

Defined in Cachix.Api.Types

FromJSON NarInfo Source # 
Instance details

Defined in Cachix.Api.Types

ToSchema NarInfo Source # 
Instance details

Defined in Cachix.Api.Types

MimeUnrender XNixNarInfo NarInfo Source # 
Instance details

Defined in Cachix.Types.ContentTypes

type Rep NarInfo Source # 
Instance details

Defined in Cachix.Api.Types

data BinaryCache Source #

Constructors

BinaryCache 
Instances
Show BinaryCache Source # 
Instance details

Defined in Cachix.Api.Types

Generic BinaryCache Source # 
Instance details

Defined in Cachix.Api.Types

Associated Types

type Rep BinaryCache :: Type -> Type #

ToJSON BinaryCache Source # 
Instance details

Defined in Cachix.Api.Types

FromJSON BinaryCache Source # 
Instance details

Defined in Cachix.Api.Types

ToSchema BinaryCache Source # 
Instance details

Defined in Cachix.Api.Types

type Rep BinaryCache Source # 
Instance details

Defined in Cachix.Api.Types

type Rep BinaryCache = D1 (MetaData "BinaryCache" "Cachix.Api.Types" "cachix-api-0.1.0.3-HMIesBjHyxfFikB1iuASsF" False) (C1 (MetaCons "BinaryCache" PrefixI True) ((S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "uri") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :*: (S1 (MetaSel (Just "publicSigningKeys") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text]) :*: S1 (MetaSel (Just "githubUsername") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))

newtype BinaryCacheCreate Source #

Constructors

BinaryCacheCreate 

newtype BinaryCacheError Source #

Constructors

BinaryCacheError 

Fields

Instances
Generic BinaryCacheError Source # 
Instance details

Defined in Cachix.Api.Types

Associated Types

type Rep BinaryCacheError :: Type -> Type #

ToJSON BinaryCacheError Source # 
Instance details

Defined in Cachix.Api.Types

FromJSON BinaryCacheError Source # 
Instance details

Defined in Cachix.Api.Types

type Rep BinaryCacheError Source # 
Instance details

Defined in Cachix.Api.Types

type Rep BinaryCacheError = D1 (MetaData "BinaryCacheError" "Cachix.Api.Types" "cachix-api-0.1.0.3-HMIesBjHyxfFikB1iuASsF" True) (C1 (MetaCons "BinaryCacheError" PrefixI True) (S1 (MetaSel (Just "error") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype NarC Source #

Hash of nar.xz file

Constructors

NarC Text 
Instances
Generic NarC Source # 
Instance details

Defined in Cachix.Api.Types

Associated Types

type Rep NarC :: Type -> Type #

Methods

from :: NarC -> Rep NarC x #

to :: Rep NarC x -> NarC #

ToHttpApiData NarC Source # 
Instance details

Defined in Cachix.Api.Types

FromHttpApiData NarC Source # 
Instance details

Defined in Cachix.Api.Types

ToSchema NarC Source # 
Instance details

Defined in Cachix.Api.Types

ToParamSchema NarC Source # 
Instance details

Defined in Cachix.Api.Types

Methods

toParamSchema :: proxy NarC -> ParamSchema t #

type Rep NarC Source # 
Instance details

Defined in Cachix.Api.Types

type Rep NarC = D1 (MetaData "NarC" "Cachix.Api.Types" "cachix-api-0.1.0.3-HMIesBjHyxfFikB1iuASsF" True) (C1 (MetaCons "NarC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype NarInfoC Source #

Store path hash

Constructors

NarInfoC Text 
Instances
Generic NarInfoC Source # 
Instance details

Defined in Cachix.Api.Types

Associated Types

type Rep NarInfoC :: Type -> Type #

Methods

from :: NarInfoC -> Rep NarInfoC x #

to :: Rep NarInfoC x -> NarInfoC #

ToHttpApiData NarInfoC Source # 
Instance details

Defined in Cachix.Api.Types

FromHttpApiData NarInfoC Source # 
Instance details

Defined in Cachix.Api.Types

ToSchema NarInfoC Source # 
Instance details

Defined in Cachix.Api.Types

ToParamSchema NarInfoC Source # 
Instance details

Defined in Cachix.Api.Types

Methods

toParamSchema :: proxy NarInfoC -> ParamSchema t #

type Rep NarInfoC Source # 
Instance details

Defined in Cachix.Api.Types

type Rep NarInfoC = D1 (MetaData "NarInfoC" "Cachix.Api.Types" "cachix-api-0.1.0.3-HMIesBjHyxfFikB1iuASsF" True) (C1 (MetaCons "NarInfoC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data User Source #

Constructors

User 
Instances
Generic User Source # 
Instance details

Defined in Cachix.Api.Types

Associated Types

type Rep User :: Type -> Type #

Methods

from :: User -> Rep User x #

to :: Rep User x -> User #

ToJSON User Source # 
Instance details

Defined in Cachix.Api.Types

FromJSON User Source # 
Instance details

Defined in Cachix.Api.Types

ToSchema User Source # 
Instance details

Defined in Cachix.Api.Types

type Rep User Source # 
Instance details

Defined in Cachix.Api.Types

type Rep User = D1 (MetaData "User" "Cachix.Api.Types" "cachix-api-0.1.0.3-HMIesBjHyxfFikB1iuASsF" False) (C1 (MetaCons "User" PrefixI True) (S1 (MetaSel (Just "fullname") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "username") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "email") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))