unison-share-api-0.0.0
Safe HaskellSafe-Inferred
LanguageHaskell2010

Unison.Server.Types

Synopsis

Documentation

type APIHeaders x = Headers '[Header "Cache-Control" String] x Source #

type APIGet c = Get '[JSON] (APIHeaders c) Source #

type Size = Int Source #

data NamespaceDetails Source #

Constructors

NamespaceDetails 

Fields

Instances

Instances details
ToJSON NamespaceDetails Source # 
Instance details

Defined in Unison.Server.Types

Generic NamespaceDetails Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep NamespaceDetails :: Type -> Type #

Show NamespaceDetails Source # 
Instance details

Defined in Unison.Server.Types

ToSchema NamespaceDetails Source # 
Instance details

Defined in Unison.Server.Types

ToSample NamespaceDetails Source # 
Instance details

Defined in Unison.Server.Types

type Rep NamespaceDetails Source # 
Instance details

Defined in Unison.Server.Types

type Rep NamespaceDetails = D1 ('MetaData "NamespaceDetails" "Unison.Server.Types" "unison-share-api-0.0.0-7lCnmLo0h1RCAMi07EAZKZ" 'False) (C1 ('MetaCons "NamespaceDetails" 'PrefixI 'True) (S1 ('MetaSel ('Just "fqn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Path) :*: (S1 ('MetaSel ('Just "hash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnisonHash) :*: S1 ('MetaSel ('Just "readme") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Doc)))))

data ExactName name ref Source #

A hash qualified name, unlike HashQualified, the hash is required

Constructors

ExactName 

Fields

Instances

Instances details
Bifoldable ExactName Source # 
Instance details

Defined in Unison.Server.Types

Methods

bifold :: Monoid m => ExactName m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> ExactName a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> ExactName a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> ExactName a b -> c #

Bifunctor ExactName Source # 
Instance details

Defined in Unison.Server.Types

Methods

bimap :: (a -> b) -> (c -> d) -> ExactName a c -> ExactName b d #

first :: (a -> b) -> ExactName a c -> ExactName b c #

second :: (b -> c) -> ExactName a b -> ExactName a c #

Bitraversable ExactName Source # 
Instance details

Defined in Unison.Server.Types

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> ExactName a b -> f (ExactName c d) #

ToCapture (Capture "fqn" (ExactName Name ShortHash)) Source # 
Instance details

Defined in Unison.Server.Types

ToParam (QueryParam "exact-name" (ExactName Name ShortHash)) Source # 
Instance details

Defined in Unison.Server.Types

Functor (ExactName name) Source # 
Instance details

Defined in Unison.Server.Types

Methods

fmap :: (a -> b) -> ExactName name a -> ExactName name b #

(<$) :: a -> ExactName name b -> ExactName name a #

(Show name, Show ref) => Show (ExactName name ref) Source # 
Instance details

Defined in Unison.Server.Types

Methods

showsPrec :: Int -> ExactName name ref -> ShowS #

show :: ExactName name ref -> String #

showList :: [ExactName name ref] -> ShowS #

(Eq name, Eq ref) => Eq (ExactName name ref) Source # 
Instance details

Defined in Unison.Server.Types

Methods

(==) :: ExactName name ref -> ExactName name ref -> Bool #

(/=) :: ExactName name ref -> ExactName name ref -> Bool #

(Ord name, Ord ref) => Ord (ExactName name ref) Source # 
Instance details

Defined in Unison.Server.Types

Methods

compare :: ExactName name ref -> ExactName name ref -> Ordering #

(<) :: ExactName name ref -> ExactName name ref -> Bool #

(<=) :: ExactName name ref -> ExactName name ref -> Bool #

(>) :: ExactName name ref -> ExactName name ref -> Bool #

(>=) :: ExactName name ref -> ExactName name ref -> Bool #

max :: ExactName name ref -> ExactName name ref -> ExactName name ref #

min :: ExactName name ref -> ExactName name ref -> ExactName name ref #

FromHttpApiData (ExactName Name ShortHash) Source # 
Instance details

Defined in Unison.Server.Types

ToParamSchema (ExactName Name ShortHash) Source # 
Instance details

Defined in Unison.Server.Types

newtype Suffixify Source #

Constructors

Suffixify 

Fields

Instances

Instances details
Generic Suffixify Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep Suffixify :: Type -> Type #

Show Suffixify Source # 
Instance details

Defined in Unison.Server.Types

Eq Suffixify Source # 
Instance details

Defined in Unison.Server.Types

Ord Suffixify Source # 
Instance details

Defined in Unison.Server.Types

FromHttpApiData Suffixify Source # 
Instance details

Defined in Unison.Server.Types

ToParamSchema Suffixify Source # 
Instance details

Defined in Unison.Server.Types

ToParam (QueryParam "suffixifyBindings" Suffixify) Source # 
Instance details

Defined in Unison.Server.Local.Endpoints.GetDefinitions

Methods

toParam :: Proxy (QueryParam "suffixifyBindings" Suffixify) -> DocQueryParam #

type Rep Suffixify Source # 
Instance details

Defined in Unison.Server.Types

type Rep Suffixify = D1 ('MetaData "Suffixify" "Unison.Server.Types" "unison-share-api-0.0.0-7lCnmLo0h1RCAMi07EAZKZ" 'True) (C1 ('MetaCons "Suffixify" 'PrefixI 'True) (S1 ('MetaSel ('Just "suffixified") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data TermDefinition Source #

Instances

Instances details
ToJSON TermDefinition Source # 
Instance details

Defined in Unison.Server.Types

Generic TermDefinition Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep TermDefinition :: Type -> Type #

Show TermDefinition Source # 
Instance details

Defined in Unison.Server.Types

Eq TermDefinition Source # 
Instance details

Defined in Unison.Server.Types

ToSchema TermDefinition Source # 
Instance details

Defined in Unison.Server.Types

type Rep TermDefinition Source # 
Instance details

Defined in Unison.Server.Types

data TypeDefinition Source #

Instances

Instances details
ToJSON TypeDefinition Source # 
Instance details

Defined in Unison.Server.Types

Generic TypeDefinition Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep TypeDefinition :: Type -> Type #

Show TypeDefinition Source # 
Instance details

Defined in Unison.Server.Types

Eq TypeDefinition Source # 
Instance details

Defined in Unison.Server.Types

ToSchema TypeDefinition Source # 
Instance details

Defined in Unison.Server.Types

type Rep TypeDefinition Source # 
Instance details

Defined in Unison.Server.Types

data DefinitionDisplayResults Source #

Instances

Instances details
ToJSON DefinitionDisplayResults Source # 
Instance details

Defined in Unison.Server.Types

Monoid DefinitionDisplayResults Source # 
Instance details

Defined in Unison.Server.Types

Semigroup DefinitionDisplayResults Source # 
Instance details

Defined in Unison.Server.Types

Generic DefinitionDisplayResults Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep DefinitionDisplayResults :: Type -> Type #

Show DefinitionDisplayResults Source # 
Instance details

Defined in Unison.Server.Types

Eq DefinitionDisplayResults Source # 
Instance details

Defined in Unison.Server.Types

ToSchema DefinitionDisplayResults Source # 
Instance details

Defined in Unison.Server.Types

ToSample DefinitionDisplayResults Source # 
Instance details

Defined in Unison.Server.Local.Endpoints.GetDefinitions

type Rep DefinitionDisplayResults Source # 
Instance details

Defined in Unison.Server.Types

type Rep DefinitionDisplayResults = D1 ('MetaData "DefinitionDisplayResults" "Unison.Server.Types" "unison-share-api-0.0.0-7lCnmLo0h1RCAMi07EAZKZ" 'False) (C1 ('MetaCons "DefinitionDisplayResults" 'PrefixI 'True) (S1 ('MetaSel ('Just "termDefinitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map UnisonHash TermDefinition)) :*: (S1 ('MetaSel ('Just "typeDefinitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map UnisonHash TypeDefinition)) :*: S1 ('MetaSel ('Just "missingDefinitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [HashQualifiedName]))))

data TermTag Source #

Constructors

Doc 
Test 
Plain 
Constructor TypeTag 

Instances

Instances details
FromJSON TermTag Source # 
Instance details

Defined in Unison.Server.Types

ToJSON TermTag Source # 
Instance details

Defined in Unison.Server.Types

Generic TermTag Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep TermTag :: Type -> Type #

Methods

from :: TermTag -> Rep TermTag x #

to :: Rep TermTag x -> TermTag #

Show TermTag Source # 
Instance details

Defined in Unison.Server.Types

Eq TermTag Source # 
Instance details

Defined in Unison.Server.Types

Methods

(==) :: TermTag -> TermTag -> Bool #

(/=) :: TermTag -> TermTag -> Bool #

Ord TermTag Source # 
Instance details

Defined in Unison.Server.Types

ToSchema TermTag Source # 
Instance details

Defined in Unison.Server.Types

type Rep TermTag Source # 
Instance details

Defined in Unison.Server.Types

type Rep TermTag = D1 ('MetaData "TermTag" "Unison.Server.Types" "unison-share-api-0.0.0-7lCnmLo0h1RCAMi07EAZKZ" 'False) ((C1 ('MetaCons "Doc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Test" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Plain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Constructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeTag))))

data TypeTag Source #

Constructors

Ability 
Data 

Instances

Instances details
FromJSON TypeTag Source # 
Instance details

Defined in Unison.Server.Types

ToJSON TypeTag Source # 
Instance details

Defined in Unison.Server.Types

Generic TypeTag Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep TypeTag :: Type -> Type #

Methods

from :: TypeTag -> Rep TypeTag x #

to :: Rep TypeTag x -> TypeTag #

Show TypeTag Source # 
Instance details

Defined in Unison.Server.Types

Eq TypeTag Source # 
Instance details

Defined in Unison.Server.Types

Methods

(==) :: TypeTag -> TypeTag -> Bool #

(/=) :: TypeTag -> TypeTag -> Bool #

Ord TypeTag Source # 
Instance details

Defined in Unison.Server.Types

ToSchema TypeTag Source # 
Instance details

Defined in Unison.Server.Types

type Rep TypeTag Source # 
Instance details

Defined in Unison.Server.Types

type Rep TypeTag = D1 ('MetaData "TypeTag" "Unison.Server.Types" "unison-share-api-0.0.0-7lCnmLo0h1RCAMi07EAZKZ" 'False) (C1 ('MetaCons "Ability" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Data" 'PrefixI 'False) (U1 :: Type -> Type))

data SemanticSyntaxDiff Source #

A type for semantic diffing of definitions. Includes special-cases for when the name in a definition has changed but the hash hasn't (rename/alias), and when the hash has changed but the name hasn't (update propagation).

Instances

Instances details
ToJSON SemanticSyntaxDiff Source # 
Instance details

Defined in Unison.Server.Types

Generic SemanticSyntaxDiff Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep SemanticSyntaxDiff :: Type -> Type #

Show SemanticSyntaxDiff Source # 
Instance details

Defined in Unison.Server.Types

Eq SemanticSyntaxDiff Source # 
Instance details

Defined in Unison.Server.Types

ToSchema SemanticSyntaxDiff Source # 
Instance details

Defined in Unison.Server.Types

type Rep SemanticSyntaxDiff Source # 
Instance details

Defined in Unison.Server.Types

data DisplayObjectDiff Source #

A diff of the syntax of a term or type

It doesn't make sense to diff builtins with ABTs, so in that case we just provide the undiffed syntax.

Instances

Instances details
Generic DisplayObjectDiff Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep DisplayObjectDiff :: Type -> Type #

Show DisplayObjectDiff Source # 
Instance details

Defined in Unison.Server.Types

Eq DisplayObjectDiff Source # 
Instance details

Defined in Unison.Server.Types

ToSchema DisplayObjectDiff Source # 
Instance details

Defined in Unison.Server.Types

type Rep DisplayObjectDiff Source # 
Instance details

Defined in Unison.Server.Types

data UnisonRef Source #

Instances

Instances details
Generic UnisonRef Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep UnisonRef :: Type -> Type #

Show UnisonRef Source # 
Instance details

Defined in Unison.Server.Types

Eq UnisonRef Source # 
Instance details

Defined in Unison.Server.Types

Ord UnisonRef Source # 
Instance details

Defined in Unison.Server.Types

type Rep UnisonRef Source # 
Instance details

Defined in Unison.Server.Types

type Rep UnisonRef = D1 ('MetaData "UnisonRef" "Unison.Server.Types" "unison-share-api-0.0.0-7lCnmLo0h1RCAMi07EAZKZ" 'False) (C1 ('MetaCons "TypeRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnisonHash)) :+: C1 ('MetaCons "TermRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnisonHash)))

data NamedTerm Source #

Instances

Instances details
FromJSON NamedTerm Source # 
Instance details

Defined in Unison.Server.Types

ToJSON NamedTerm Source # 
Instance details

Defined in Unison.Server.Types

Generic NamedTerm Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep NamedTerm :: Type -> Type #

Show NamedTerm Source # 
Instance details

Defined in Unison.Server.Types

Eq NamedTerm Source # 
Instance details

Defined in Unison.Server.Types

ToSchema NamedTerm Source # 
Instance details

Defined in Unison.Server.Types

type Rep NamedTerm Source # 
Instance details

Defined in Unison.Server.Types

type Rep NamedTerm = D1 ('MetaData "NamedTerm" "Unison.Server.Types" "unison-share-api-0.0.0-7lCnmLo0h1RCAMi07EAZKZ" 'False) (C1 ('MetaCons "NamedTerm" 'PrefixI 'True) ((S1 ('MetaSel ('Just "termName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashQualified Name)) :*: S1 ('MetaSel ('Just "termHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortHash)) :*: (S1 ('MetaSel ('Just "termType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SyntaxText)) :*: S1 ('MetaSel ('Just "termTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TermTag))))

data NamedType Source #

Instances

Instances details
FromJSON NamedType Source # 
Instance details

Defined in Unison.Server.Types

ToJSON NamedType Source # 
Instance details

Defined in Unison.Server.Types

Generic NamedType Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep NamedType :: Type -> Type #

Show NamedType Source # 
Instance details

Defined in Unison.Server.Types

Eq NamedType Source # 
Instance details

Defined in Unison.Server.Types

ToSchema NamedType Source # 
Instance details

Defined in Unison.Server.Types

type Rep NamedType Source # 
Instance details

Defined in Unison.Server.Types

type Rep NamedType = D1 ('MetaData "NamedType" "Unison.Server.Types" "unison-share-api-0.0.0-7lCnmLo0h1RCAMi07EAZKZ" 'False) (C1 ('MetaCons "NamedType" 'PrefixI 'True) (S1 ('MetaSel ('Just "typeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashQualified Name)) :*: (S1 ('MetaSel ('Just "typeHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortHash) :*: S1 ('MetaSel ('Just "typeTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeTag))))

discard :: Applicative m => a -> m () Source #

newtype ProjectBranchNameParam Source #

Instances

Instances details
Generic ProjectBranchNameParam Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep ProjectBranchNameParam :: Type -> Type #

Show ProjectBranchNameParam Source # 
Instance details

Defined in Unison.Server.Types

Eq ProjectBranchNameParam Source # 
Instance details

Defined in Unison.Server.Types

FromHttpApiData ProjectBranchNameParam Source #

Parses URL escaped project and branch names, e.g. `unison%2Fbase%2Fmain` or `unison%2Fbase%2F@runarorama%2Fmain`

Instance details

Defined in Unison.Server.Types

ToParamSchema ProjectBranchNameParam Source # 
Instance details

Defined in Unison.Server.Types

ToCapture (Capture "project-and-branch" ProjectBranchNameParam) Source # 
Instance details

Defined in Unison.Server.Types

Methods

toCapture :: Proxy (Capture "project-and-branch" ProjectBranchNameParam) -> DocCapture #

ToParam (QueryParam "project-and-branch" ProjectBranchNameParam) Source # 
Instance details

Defined in Unison.Server.Types

Methods

toParam :: Proxy (QueryParam "project-and-branch" ProjectBranchNameParam) -> DocQueryParam #

type Rep ProjectBranchNameParam Source # 
Instance details

Defined in Unison.Server.Types

type Rep ProjectBranchNameParam = D1 ('MetaData "ProjectBranchNameParam" "Unison.Server.Types" "unison-share-api-0.0.0-7lCnmLo0h1RCAMi07EAZKZ" 'True) (C1 ('MetaCons "ProjectBranchNameParam" 'PrefixI 'True) (S1 ('MetaSel ('Just "unProjectBranchNameParam") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ProjectAndBranch ProjectName ProjectBranchName))))

data TermDiffResponse Source #

Instances

Instances details
ToJSON TermDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

Generic TermDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep TermDiffResponse :: Type -> Type #

Show TermDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

Eq TermDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

ToSchema TermDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

ToSample TermDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

type Rep TermDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

data TypeDiffResponse Source #

Instances

Instances details
ToJSON TypeDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

Generic TypeDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

Associated Types

type Rep TypeDiffResponse :: Type -> Type #

Show TypeDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

Eq TypeDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

ToSchema TypeDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

ToSample TypeDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

type Rep TypeDiffResponse Source # 
Instance details

Defined in Unison.Server.Types

type RequiredQueryParam = QueryParam' '[Required, Strict] Source #

Servant utility for a query param that's required, providing a useful error message if it's missing.