Predict the correct size of full images

This commit is contained in:
Emi Simpson 2022-11-09 17:44:35 -05:00
parent 3802543623
commit 387e7d1b47
Signed by: Emi
GPG key ID: A12F2C2FFDC3D847
6 changed files with 62 additions and 28 deletions

View file

@ -16,6 +16,8 @@ message Image {
string thumb_url = 3; string thumb_url = 3;
string blurhash = 4; string blurhash = 4;
Format format = 5; Format format = 5;
uint32 width = 6;
uint32 height = 7;
} }
message Index { message Index {

View file

@ -18,6 +18,8 @@ body {
.thumbnail-card { .thumbnail-card {
height: 400px; height: 400px;
width: 400px; width: 400px;
}
.blurhash-frame {
background-size: cover; background-size: cover;
display: grid; display: grid;
align-items: center; align-items: center;

View file

@ -23,6 +23,7 @@ import Data.ArrayBuffer.Types (ArrayBuffer)
import Data.Filterable (partitionMap) import Data.Filterable (partitionMap)
import Data.String (drop) import Data.String (drop)
import Parsing (runParserT) import Parsing (runParserT)
import Protobuf.Internal.Prelude (toInt)
import Web.File.Url (createObjectURL) import Web.File.Url (createObjectURL)
import Web.HTML (window) as HTML import Web.HTML (window) as HTML
import Web.HTML.Window (location) import Web.HTML.Window (location)
@ -60,11 +61,15 @@ convertImageFromProtobuf protoimage = let protoimage' = unwrap protoimage in do
thumbUrl <- note (IndexMissingField "images[].thumb_url") protoimage'.thumb_url thumbUrl <- note (IndexMissingField "images[].thumb_url") protoimage'.thumb_url
blurhash <- note (IndexMissingField "images[].blurhash") protoimage'.blurhash blurhash <- note (IndexMissingField "images[].blurhash") protoimage'.blurhash
format <- note (IndexMissingField "images[].format") protoimage'.format format <- note (IndexMissingField "images[].format") protoimage'.format
width' <- note (IndexMissingField "images[].width") protoimage'.width
height' <- note (IndexMissingField "images[].height") protoimage'.height
let blurhashUrl = decodeBlurhash32 blurhash let blurhashUrl = decodeBlurhash32 blurhash
let key = hush <$> (importKey =<< liftEffect (databuffToBuffer $ unwrap rawKey)) let key = hush <$> (importKey =<< liftEffect (databuffToBuffer $ unwrap rawKey))
let thumb = Unloaded thumbUrl let thumb = Unloaded thumbUrl
let full = Unloaded fullUrl let full = Unloaded fullUrl
pure { key, blurhashUrl, format, thumb, full } let width = toInt width'
let height = toInt height'
pure { key, blurhashUrl, format, thumb, full, width, height }
convertIndexFromProtobuf :: Format.Index -> Model convertIndexFromProtobuf :: Format.Index -> Model
convertIndexFromProtobuf protoindex = convertIndexFromProtobuf protoindex =

View file

@ -5,7 +5,7 @@ import Prelude
import AviaryFormat.Format (Format(..)) as Format import AviaryFormat.Format (Format(..)) as Format
import Crypto.Subtle.Key.Types (CryptoKey) import Crypto.Subtle.Key.Types (CryptoKey)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe)
import Effect.Aff (Aff) import Effect.Aff (Aff)
data GalleryError data GalleryError
@ -45,6 +45,8 @@ type Image =
, format :: Format.Format , format :: Format.Format
, thumb :: ImageData , thumb :: ImageData
, full :: ImageData , full :: ImageData
, width :: Int
, height :: Int
} }
type LoadedGallery = type LoadedGallery =
@ -58,17 +60,6 @@ data Model
= GError GalleryError = GError GalleryError
| GLoaded LoadedGallery | GLoaded LoadedGallery
imgOrBlurhash :: (Image -> ImageData) -> Image -> Maybe String
imgOrBlurhash idealData image = case idealData image of
ILoaded url -> Just url
_ -> image.blurhashUrl
thumbOrBlurhash :: Image -> Maybe String
thumbOrBlurhash = imgOrBlurhash _.thumb
fullOrBlurhash :: Image -> Maybe String
fullOrBlurhash = imgOrBlurhash _.full
instance showGalleryError :: Show GalleryError where instance showGalleryError :: Show GalleryError where
show (UnexpectedError message) = show (UnexpectedError message) =
"Something that should be impossible just happened! Please open up a new issue " "Something that should be impossible just happened! Please open up a new issue "

View file

@ -3,12 +3,10 @@ module Aviary.UI where
import Prelude import Prelude
import Aviary.Logic (fetchFull, fetchThumb) import Aviary.Logic (fetchFull, fetchThumb)
import Aviary.Model ( fullOrBlurhash import Aviary.Model ( GalleryError(..)
, GalleryError(..)
, Image , Image
, ImageData(..) , ImageData(..)
, Model(..) , Model(..)
, thumbOrBlurhash
) )
import Control.Parallel (parSequence_) import Control.Parallel (parSequence_)
@ -34,18 +32,21 @@ component initialState = H.mkComponent
, eval: H.mkEval $ H.defaultEval { handleAction = update, initialize = Just LoadThumbs } , eval: H.mkEval $ H.defaultEval { handleAction = update, initialize = Just LoadThumbs }
} }
backgroundUrl :: forall r i. String -> HP.IProp (style :: String | r) i backgroundUrl :: String -> String
backgroundUrl url = HP.style $ "background-image: url(" <> url <> ");" backgroundUrl url = "background-image: url(" <> url <> ");"
widthHeight :: Int -> Int -> String
widthHeight w h = "width:" <> (show w) <> "px;height:" <> (show h) <> "px;"
renderThumbnail :: forall m. Int -> Image -> H.ComponentHTML Event () m renderThumbnail :: forall m. Int -> Image -> H.ComponentHTML Event () m
renderThumbnail pos image = renderThumbnail pos image =
HH.div HH.div
( (
[ HP.class_ $ ClassName "thumbnail-card" [ HP.classes $ ClassName <$> ["thumbnail-card", "blurhash-frame"]
, HE.onClick \_ -> Focus pos , HE.onClick \_ -> Focus pos
] ]
<> <>
maybe [] (backgroundUrl >>> pure) (image.blurhashUrl) maybe [] (backgroundUrl >>> HP.style >>> pure) (image.blurhashUrl)
) )
case image.thumb of case image.thumb of
Unloaded _ -> Unloaded _ ->
@ -69,16 +70,35 @@ renderThumbnail pos image =
renderFocused :: forall m. Image -> H.ComponentHTML Event () m renderFocused :: forall m. Image -> H.ComponentHTML Event () m
renderFocused image = renderFocused image =
HH.div HH.div
[ HP.id $ "focused-panel" [ HP.id "focused-panel"
, HE.onClick \_ -> Unfocus , HE.onClick \_ -> Unfocus
] ]
( [ HH.img $ [ HH.div
maybe [] (HP.src >>> pure) (fullOrBlurhash image) [ HP.style
] <> case image.full of ( widthHeight image.width image.height
Unloaded _ -> [HH.p_ [HH.text "Loading..."]] <> maybe "" backgroundUrl (image.blurhashUrl)
IError e -> [HH.p_ [HH.text $ "Error! " <> (show e)]] )
_ -> [] , HP.class_ $ ClassName "blurhash-frame"
) ]
case image.full of
Unloaded _ ->
[ HH.span
[ HP.class_ $ ClassName "loading-msg"
]
[ HH.text "Loading..."
]
]
IError e ->
[ HH.span
[ HP.class_ $ ClassName "error-msg"
]
[ HH.text $ "Error! " <> (show e)
]
]
ILoaded url ->
[ HH.img [HP.src url]
]
]
setImage :: (Image -> Image) -> Int -> Model -> Model setImage :: (Image -> Image) -> Int -> Model -> Model
setImage _ _ (GError e) = (GError e) setImage _ _ (GError e) = (GError e)

View file

@ -19,6 +19,8 @@ type ImageRow =
, thumb_url :: Prelude.Maybe String , thumb_url :: Prelude.Maybe String
, blurhash :: Prelude.Maybe String , blurhash :: Prelude.Maybe String
, format :: Prelude.Maybe Format , format :: Prelude.Maybe Format
, width :: Prelude.Maybe Prelude.UInt
, height :: Prelude.Maybe Prelude.UInt
, __unknown_fields :: Array Prelude.UnknownField , __unknown_fields :: Array Prelude.UnknownField
) )
type ImageR = Record ImageRow type ImageR = Record ImageRow
@ -34,6 +36,8 @@ putImage (Image r) = do
Prelude.putOptional 3 r.thumb_url Prelude.isDefault Prelude.encodeStringField Prelude.putOptional 3 r.thumb_url Prelude.isDefault Prelude.encodeStringField
Prelude.putOptional 4 r.blurhash Prelude.isDefault Prelude.encodeStringField Prelude.putOptional 4 r.blurhash Prelude.isDefault Prelude.encodeStringField
Prelude.putOptional 5 r.format Prelude.isDefault Prelude.putEnumField Prelude.putOptional 5 r.format Prelude.isDefault Prelude.putEnumField
Prelude.putOptional 6 r.width Prelude.isDefault Prelude.encodeUint32Field
Prelude.putOptional 7 r.height Prelude.isDefault Prelude.encodeUint32Field
Prelude.traverse_ Prelude.putFieldUnknown r.__unknown_fields Prelude.traverse_ Prelude.putFieldUnknown r.__unknown_fields
parseImage :: forall m. Prelude.MonadEffect m => Prelude.MonadRec m => Prelude.ByteLength -> Prelude.ParserT Prelude.DataView m Image parseImage :: forall m. Prelude.MonadEffect m => Prelude.MonadRec m => Prelude.ByteLength -> Prelude.ParserT Prelude.DataView m Image
@ -59,6 +63,12 @@ parseImage length = Prelude.label "Image / " $
parseField 5 Prelude.VarInt = Prelude.label "format / " $ do parseField 5 Prelude.VarInt = Prelude.label "format / " $ do
x <- Prelude.parseEnum x <- Prelude.parseEnum
pure $ Prelude.modify (Prelude.Proxy :: Prelude.Proxy "format") $ \_ -> Prelude.Just x pure $ Prelude.modify (Prelude.Proxy :: Prelude.Proxy "format") $ \_ -> Prelude.Just x
parseField 6 Prelude.VarInt = Prelude.label "width / " $ do
x <- Prelude.decodeUint32
pure $ Prelude.modify (Prelude.Proxy :: Prelude.Proxy "width") $ \_ -> Prelude.Just x
parseField 7 Prelude.VarInt = Prelude.label "height / " $ do
x <- Prelude.decodeUint32
pure $ Prelude.modify (Prelude.Proxy :: Prelude.Proxy "height") $ \_ -> Prelude.Just x
parseField fieldNumber wireType = Prelude.parseFieldUnknown fieldNumber wireType parseField fieldNumber wireType = Prelude.parseFieldUnknown fieldNumber wireType
defaultImage :: ImageR defaultImage :: ImageR
@ -68,6 +78,8 @@ defaultImage =
, thumb_url: Prelude.Nothing , thumb_url: Prelude.Nothing
, blurhash: Prelude.Nothing , blurhash: Prelude.Nothing
, format: Prelude.Nothing , format: Prelude.Nothing
, width: Prelude.Nothing
, height: Prelude.Nothing
, __unknown_fields: [] , __unknown_fields: []
} }
@ -81,6 +93,8 @@ mergeImage (Image l) (Image r) = Image
, thumb_url: Prelude.alt l.thumb_url r.thumb_url , thumb_url: Prelude.alt l.thumb_url r.thumb_url
, blurhash: Prelude.alt l.blurhash r.blurhash , blurhash: Prelude.alt l.blurhash r.blurhash
, format: Prelude.alt l.format r.format , format: Prelude.alt l.format r.format
, width: Prelude.alt l.width r.width
, height: Prelude.alt l.height r.height
, __unknown_fields: r.__unknown_fields <> l.__unknown_fields , __unknown_fields: r.__unknown_fields <> l.__unknown_fields
} }