silvi-0.0.4: A generator for different kinds of logs.

Safe HaskellNone
LanguageHaskell2010

Silvi.Record

Synopsis

Documentation

data Field Source #

Different types present in logs.

Constructors

FieldBracketNum

Number that appears before many logs, in the form of "X"

FieldHttpMethod

More explicit name for Network.HTTP.Types.Method

FieldHttpStatus

More explicit name for Network.HTTP.Types.Status

FieldHttpVersion

More explicit name for Network.HTTP.Types.Version

FieldUrl

a url, e.g. "https://hackage.haskell.org"

FieldUserId

userId as Text

FieldObjSize

usually requested resource size

FieldIp

FieldIp present in log

FieldTimestamp

Timestamp

Instances

Bounded Field Source # 
Enum Field Source # 
Eq Field Source # 

Methods

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

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

Ord Field Source # 

Methods

compare :: Field -> Field -> Ordering #

(<) :: Field -> Field -> Bool #

(<=) :: Field -> Field -> Bool #

(>) :: Field -> Field -> Bool #

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

max :: Field -> Field -> Field #

min :: Field -> Field -> Field #

Read Field Source # 
Show Field Source # 

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

Generic Field Source # 

Associated Types

type Rep Field :: * -> * #

Methods

from :: Field -> Rep Field x #

to :: Rep Field x -> Field #

ShowForall Field Value Source # 

Methods

showsPrecForall :: Int -> f a -> ShowS #

Reify Field FieldBracketNum Source # 
Reify Field FieldHttpMethod Source # 
Reify Field FieldHttpStatus Source # 
Reify Field FieldHttpVersion Source # 
Reify Field FieldUrl Source # 

Methods

reify :: Sing FieldUrl a #

Reify Field FieldUserId Source # 

Methods

reify :: Sing FieldUserId a #

Reify Field FieldObjSize Source # 

Methods

reify :: Sing FieldObjSize a #

Reify Field FieldIp Source # 

Methods

reify :: Sing FieldIp a #

Reify Field FieldTimestamp Source # 
type Rep Field Source # 
type Rep Field = D1 * (MetaData "Field" "Silvi.Record" "silvi-0.0.4-ILJ74z4U3mdKGV8aVtkZg5" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "FieldBracketNum" PrefixI False) (U1 *)) (C1 * (MetaCons "FieldHttpMethod" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "FieldHttpStatus" PrefixI False) (U1 *)) (C1 * (MetaCons "FieldHttpVersion" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "FieldUrl" PrefixI False) (U1 *)) (C1 * (MetaCons "FieldUserId" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "FieldObjSize" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FieldIp" PrefixI False) (U1 *)) (C1 * (MetaCons "FieldTimestamp" PrefixI False) (U1 *))))))
type Sing Field Source # 

data Rec k (a :: k -> Type) (b :: [k]) :: forall k. (k -> Type) -> [k] -> Type where #

Constructors

RecNil :: Rec k a ([] k) 
RecCons :: Rec k a ((:) k r rs) 

Instances

TestCoercion k f => TestCoercion [k] (Rec k f) 

Methods

testCoercion :: f a -> f b -> Maybe (Coercion (Rec k f) a b) #

TestEquality k f => TestEquality [k] (Rec k f) 

Methods

testEquality :: f a -> f b -> Maybe ((Rec k f :~: a) b) #

EqForall k f => EqForall [k] (Rec k f) 

Methods

eqForall :: f a -> f a -> Bool #

OrdForall k f => OrdForall [k] (Rec k f) 

Methods

compareForall :: f a -> f a -> Ordering #

ShowForall k f => ShowForall [k] (Rec k f) 

Methods

showsPrecForall :: Int -> f a -> ShowS #

HashableForall k f => HashableForall [k] (Rec k f) 

Methods

hashWithSaltForall :: Int -> f a -> Int #

ToJSONForall k f => ToJSONForall [k] (Rec k f) 

Methods

toJSONForall :: f a -> Value #

FromJSONForall k f => FromJSONForall [k] (Rec k f) 

Methods

parseJSONForall :: Sing (Rec k f) a -> Value -> Parser (f a) #

FromJSONExists k f => FromJSONExists [k] (Rec k f) 

Methods

parseJSONExists :: Value -> Parser (Exists (Rec k f) f) #

SemigroupForall k f => SemigroupForall [k] (Rec k f) 

Methods

sappendForall :: f a -> f a -> f a #

StorableForall k f => StorableForall [k] (Rec k f) 

Methods

peekForall :: Sing (Rec k f) a -> Ptr (f a) -> IO (f a) #

pokeForall :: Ptr (f a) -> f a -> IO () #

sizeOfFunctorForall :: f a -> Int #

sizeOfForall :: Proxy (Rec k f -> Type) f -> Sing (Rec k f) a -> Int #

MonoidForall k f => MonoidForall [k] (Rec k f) 

Methods

memptyForall :: Sing (Rec k f) a -> f a #

EqForall k f => Eq (Rec k f as) 

Methods

(==) :: Rec k f as -> Rec k f as -> Bool #

(/=) :: Rec k f as -> Rec k f as -> Bool #

OrdForall k f => Ord (Rec k f as) 

Methods

compare :: Rec k f as -> Rec k f as -> Ordering #

(<) :: Rec k f as -> Rec k f as -> Bool #

(<=) :: Rec k f as -> Rec k f as -> Bool #

(>) :: Rec k f as -> Rec k f as -> Bool #

(>=) :: Rec k f as -> Rec k f as -> Bool #

max :: Rec k f as -> Rec k f as -> Rec k f as #

min :: Rec k f as -> Rec k f as -> Rec k f as #

ShowForall k f => Show (Rec k f as) 

Methods

showsPrec :: Int -> Rec k f as -> ShowS #

show :: Rec k f as -> String #

showList :: [Rec k f as] -> ShowS #

SemigroupForall k f => Semigroup (Rec k f as) 

Methods

(<>) :: Rec k f as -> Rec k f as -> Rec k f as #

sconcat :: NonEmpty (Rec k f as) -> Rec k f as #

stimes :: Integral b => b -> Rec k f as -> Rec k f as #

(MonoidForall k f, Reify [k] as) => Monoid (Rec k f as) 

Methods

mempty :: Rec k f as #

mappend :: Rec k f as -> Rec k f as -> Rec k f as #

mconcat :: [Rec k f as] -> Rec k f as #

HashableForall k f => Hashable (Rec k f as) 

Methods

hashWithSalt :: Int -> Rec k f as -> Int #

hash :: Rec k f as -> Int #

ToJSONForall k f => ToJSON (Rec k f as) 

Methods

toJSON :: Rec k f as -> Value #

toEncoding :: Rec k f as -> Encoding #

toJSONList :: [Rec k f as] -> Value #

toEncodingList :: [Rec k f as] -> Encoding #

(FromJSONForall k f, Reify [k] as) => FromJSON (Rec k f as) 

Methods

parseJSON :: Value -> Parser (Rec k f as) #

parseJSONList :: Value -> Parser [Rec k f as] #

(StorableForall k f, Reify [k] as) => Storable (Rec k f as) 

Methods

sizeOf :: Rec k f as -> Int #

alignment :: Rec k f as -> Int #

peekElemOff :: Ptr (Rec k f as) -> Int -> IO (Rec k f as) #

pokeElemOff :: Ptr (Rec k f as) -> Int -> Rec k f as -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec k f as) #

pokeByteOff :: Ptr b -> Int -> Rec k f as -> IO () #

peek :: Ptr (Rec k f as) -> IO (Rec k f as) #

poke :: Ptr (Rec k f as) -> Rec k f as -> IO () #